Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type CDir = ()
- type CDirent = ()
- type DirStream = Ptr CDir
- openDirStream :: RawFilePath -> IO DirStream
- c_opendir :: CString -> IO (Ptr CDir)
- getDirectoryContentsAndAttrs :: RawFilePath -> IO [(RawFilePath, CUInt)]
- data Step s o r
- data Stream o m r = forall s . Stream (s -> m (Step s o r)) (m s)
- streamDirectoryAndAttrs :: RawFilePath -> Stream (RawFilePath, CUInt) IO ()
- sourceDirectory :: MonadSafe m => RawFilePath -> Producer (RawFilePath, CUInt) m ()
- readDirStream :: DirStream -> Ptr CDirent -> IO (RawFilePath, CUInt)
- statIsDirectory :: RawFilePath -> IO Bool
- statFilePath :: Bool -> Bool -> RawFilePath -> IO (Maybe FileStatus)
- getStat :: Maybe Bool -> FileEntry f -> IO (Maybe (FileStatus, FileEntry f))
- c_readdir :: Ptr CDir -> Ptr (Ptr CDirent) -> IO CInt
- c_freeDirEnt :: Ptr CDirent -> IO ()
- c_readdir_r :: Ptr CDir -> Ptr CDirent -> Ptr (Ptr CDirent) -> IO CInt
- c_sizeof_dirent :: CUInt
- d_name :: Ptr CDirent -> IO CString
- d_namlen :: Ptr CDirent -> IO CUInt
- d_type :: Ptr CDirent -> IO CUInt
- closeDirStream :: DirStream -> IO ()
- c_closedir :: Ptr CDir -> IO CInt
Documentation
openDirStream :: RawFilePath -> IO DirStream Source
openDirStream dir
calls opendir
to obtain a directory stream for
dir
.
getDirectoryContentsAndAttrs :: RawFilePath -> IO [(RawFilePath, CUInt)] Source
streamDirectoryAndAttrs :: RawFilePath -> Stream (RawFilePath, CUInt) IO () Source
sourceDirectory :: MonadSafe m => RawFilePath -> Producer (RawFilePath, CUInt) m () Source
readDirStream :: DirStream -> Ptr CDirent -> IO (RawFilePath, CUInt) Source
readDirStream dp
calls readdir
to obtain the next directory entry
(struct dirent
) for the open directory stream dp
, and returns the
d_name
member of that structure.
statIsDirectory :: RawFilePath -> IO Bool Source
statFilePath :: Bool -> Bool -> RawFilePath -> IO (Maybe FileStatus) Source
getStat :: Maybe Bool -> FileEntry f -> IO (Maybe (FileStatus, FileEntry f)) Source
Get the current status for the file. If the status being requested is already cached in the entry information, simply return it from there.
c_freeDirEnt :: Ptr CDirent -> IO () Source
closeDirStream :: DirStream -> IO () Source
closeDirStream dp
calls closedir
to close the directory stream dp
.