System.FilePath.FindCompat
- data FileInfo = FileInfo {
- infoPath :: FilePath
- infoDepth :: Int
- infoStatus :: FileStatus
- data FileType
- = BlockDevice
- | CharacterDevice
- | NamedPipe
- | RegularFile
- | Directory
- | SymbolicLink
- | Socket
- | Unknown
- fileType :: FindClause FileType
- statusType :: FileStatus -> FileType
- mkFI :: FilePath -> Int -> FileStatus -> FileInfo
- newtype FindClause a = FC {}
- evalClause :: FindClause a -> FileInfo -> a
- evalFI :: FindClause a -> FilePath -> Int -> FileStatus -> a
- mkFindClause :: (FileInfo -> (a, FileInfo)) -> FindClause a
- fileInfo :: FindClause FileInfo
- fileStatus :: FindClause FileStatus
- type FilterPredicate = FindClause Bool
- type RecursionPredicate = FindClause Bool
- getDirContents :: FilePath -> IO [FilePath]
- findWithHandler :: (FilePath -> SomeException -> IO [FilePath]) -> RecursionPredicate -> FilterPredicate -> FilePath -> IO [FilePath]
- find :: RecursionPredicate -> FilterPredicate -> FilePath -> IO [FilePath]
- always :: FindClause Bool
- filePath :: FindClause FilePath
- liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m c
- (==?) :: Eq a => FindClause a -> a -> FindClause Bool
- (/=?) :: Eq a => FindClause a -> a -> FindClause Bool
- (>?) :: Ord a => FindClause a -> a -> FindClause Bool
- (<?) :: Ord a => FindClause a -> a -> FindClause Bool
- (>=?) :: Ord a => FindClause a -> a -> FindClause Bool
- (<=?) :: Ord a => FindClause a -> a -> FindClause Bool
- (.&.?) :: Bits a => FindClause a -> a -> FindClause a
- (&&?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
- (||?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
Documentation
Information collected during the traversal of a directory.
Constructors
| FileInfo | |
Fields
| |
statusType :: FileStatus -> FileTypeSource
Return the type of a file. This is much more useful for case
analysis than the usual functions on FileStatus values.
newtype FindClause a Source
Monadic container for file information, allowing for clean
construction of combinators. Wraps the State monad, but doesn't
allow get or put.
Instances
evalClause :: FindClause a -> FileInfo -> aSource
Run the given FindClause on the given FileInfo and return its
result. This can be useful if you are writing a function to pass
to fold.
Example:
myFoldFunc :: a ->FileInfo-> a myFoldFunc a i = let useThisFile =evalClause(fileName==?"foo") i in if useThisFile then fiddleWith a else a
evalFI :: FindClause a -> FilePath -> Int -> FileStatus -> aSource
mkFindClause :: (FileInfo -> (a, FileInfo)) -> FindClause aSource
fileInfo :: FindClause FileInfoSource
Return the current FileInfo.
fileStatus :: FindClause FileStatusSource
Return the FileStatus for the current file.
type FilterPredicate = FindClause BoolSource
getDirContents :: FilePath -> IO [FilePath]Source
List the files in the given directory, sorted, and without "." or "..".
Arguments
| :: (FilePath -> SomeException -> IO [FilePath]) | error handler |
| -> RecursionPredicate | control recursion into subdirectories |
| -> FilterPredicate | decide whether a file appears in the result |
| -> FilePath | directory to start searching |
| -> IO [FilePath] | files that matched the |
Search a directory recursively, with recursion controlled by a
RecursionPredicate. Lazily return a sorted list of all files
matching the given FilterPredicate. Any errors that occur are
dealt with by the given handler.
Arguments
| :: RecursionPredicate | control recursion into subdirectories |
| -> FilterPredicate | decide whether a file appears in the result |
| -> FilePath | directory to start searching |
| -> IO [FilePath] | files that matched the |
Search a directory recursively, with recursion controlled by a
RecursionPredicate. Lazily return a sorted list of all files
matching the given FilterPredicate. Any errors that occur are
ignored, with warnings printed to stderr.
always :: FindClause BoolSource
Unconditionally return True.
filePath :: FindClause FilePathSource
Return the name of the file being visited.
liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m cSource
Lift a binary operator into the FindClause monad, so that it
becomes a combinator. The left hand side of the combinator should
be a , while the right remains a normal value of
type FindClause aa.
These are lifted versions of the most commonly used binary
operators. They have the same fixities and associativities as
their unlifted counterparts. They are lifted using liftOp, like
so:
(==?) =liftOp(==)
(==?) :: Eq a => FindClause a -> a -> FindClause BoolSource
(/=?) :: Eq a => FindClause a -> a -> FindClause BoolSource
(>?) :: Ord a => FindClause a -> a -> FindClause BoolSource
(<?) :: Ord a => FindClause a -> a -> FindClause BoolSource
(>=?) :: Ord a => FindClause a -> a -> FindClause BoolSource
(<=?) :: Ord a => FindClause a -> a -> FindClause BoolSource
(.&.?) :: Bits a => FindClause a -> a -> FindClause aSource
This operator is useful to check if bits are set in a
T.FileMode.
(&&?) :: FindClause Bool -> FindClause Bool -> FindClause BoolSource
(||?) :: FindClause Bool -> FindClause Bool -> FindClause BoolSource