1
1
{-# LANGUAGE CApiFFI #-}
2
2
{-# LANGUAGE NondecreasingIndentation #-}
3
- {-# LANGUAGE OverloadedStrings #-}
4
3
{-# LANGUAGE Safe #-}
5
4
6
5
-----------------------------------------------------------------------------
@@ -29,26 +28,10 @@ module System.Posix.Directory.ByteString (
29
28
createDirectory , removeDirectory ,
30
29
31
30
-- * Reading directories
32
- DirStream , DirStreamWithPath ,
33
- fromDirStreamWithPath ,
34
- DirType ( UnknownType
35
- , NamedPipeType
36
- , CharacterDeviceType
37
- , DirectoryType
38
- , BlockDeviceType
39
- , RegularFileType
40
- , SymbolicLinkType
41
- , SocketType
42
- , WhiteoutType
43
- ),
44
- isUnknownType , isBlockDeviceType , isCharacterDeviceType , isNamedPipeType ,
45
- isRegularFileType , isDirectoryType , isSymbolicLinkType , isSocketType ,
46
- isWhiteoutType ,
31
+ DirStream ,
47
32
openDirStream ,
48
- openDirStreamWithPath ,
49
33
readDirStream ,
50
34
readDirStreamMaybe ,
51
- readDirStreamWithType ,
52
35
rewindDirStream ,
53
36
closeDirStream ,
54
37
DirStreamOffset ,
@@ -65,18 +48,15 @@ module System.Posix.Directory.ByteString (
65
48
changeWorkingDirectoryFd ,
66
49
) where
67
50
51
+ import Control.Monad ((>=>) )
68
52
import Data.Maybe
69
53
import System.Posix.Types
70
54
import Foreign
71
55
import Foreign.C
72
56
73
57
import Data.ByteString.Char8 as BC
74
- #if !MIN_VERSION_base(4,11,0)
75
- import Data.Monoid ((<>) )
76
- #endif
77
58
78
59
import System.Posix.Directory.Common
79
- import System.Posix.Files.ByteString
80
60
import System.Posix.ByteString.FilePath
81
61
82
62
-- | @createDirectory dir mode@ calls @mkdir@ to
@@ -100,11 +80,6 @@ openDirStream name =
100
80
dirp <- throwErrnoPathIfNullRetry " openDirStream" name $ c_opendir s
101
81
return (DirStream dirp)
102
82
103
- -- | A version of 'openDirStream' where the path of the directory is stored in
104
- -- the returned 'DirStreamWithPath'.
105
- openDirStreamWithPath :: RawFilePath -> IO (DirStreamWithPath RawFilePath )
106
- openDirStreamWithPath name = toDirStreamWithPath name <$> openDirStream name
107
-
108
83
foreign import capi unsafe " HsUnix.h opendir"
109
84
c_opendir :: CString -> IO (Ptr CDir )
110
85
@@ -125,33 +100,7 @@ readDirStream = fmap (fromMaybe BC.empty) . readDirStreamMaybe
125
100
-- structure wrapped in a @Just d_name@ if an entry was read and @Nothing@ if
126
101
-- the end of the directory stream was reached.
127
102
readDirStreamMaybe :: DirStream -> IO (Maybe RawFilePath )
128
- readDirStreamMaybe = readDirStreamWith
129
- (\ (DirEnt dEnt) -> d_name dEnt >>= peekFilePath)
130
-
131
- -- | @readDirStreamWithType dp@ calls @readdir@ to obtain the
132
- -- next directory entry (@struct dirent@) for the open directory
133
- -- stream @dp@. It returns the @d_name@ member of that
134
- -- structure together with the entry's type (@d_type@) wrapped in a
135
- -- @Just (d_name, d_type)@ if an entry was read and @Nothing@ if
136
- -- the end of the directory stream was reached.
137
- --
138
- -- __Note__: The returned 'DirType' has some limitations; Please see its
139
- -- documentation.
140
- readDirStreamWithType :: DirStreamWithPath RawFilePath -> IO (Maybe (RawFilePath , DirType ))
141
- readDirStreamWithType (DirStreamWithPath (base, ptr)) = readDirStreamWith
142
- (\ (DirEnt dEnt) -> do
143
- name <- d_name dEnt >>= peekFilePath
144
- let getStat = getFileStatus (base <> " /" <> name)
145
- dtype <- d_type dEnt >>= getRealDirType getStat . DirType
146
- return (name, dtype)
147
- )
148
- (DirStream ptr)
149
-
150
- foreign import ccall unsafe " __hscore_d_name"
151
- d_name :: Ptr CDirent -> IO CString
152
-
153
- foreign import ccall unsafe " __hscore_d_type"
154
- d_type :: Ptr CDirent -> IO CChar
103
+ readDirStreamMaybe = readDirStreamWith (dirEntName >=> peekFilePath)
155
104
156
105
157
106
-- | @getWorkingDirectory@ calls @getcwd@ to obtain the name
0 commit comments