FileManip-0.1: Expressive file and directory manipulation for Haskell.ContentsIndex
System.FilePath.Find
PortabilityUnix-like systems (requires newtype deriving)
Stabilityunstable
MaintainerBryan O'Sullivan <bos@serpentine.com>
Contents
Simple entry points
More expressive entry points
Helper functions
Combinators for controlling recursion and filtering behaviour
Combinator versions of FileStatus functions from System.Posix.Files
Convenience combinators for file status
Combinators that operate on symbolic links
Common binary operators, lifted as combinators
Combinators for gluing clauses together
Description

This module provides functions for traversing a filesystem hierarchy. The find function generates a lazy list of matching files, while fold performs a left fold.

Both find and fold allow fine control over recursion, using the FindClause type. This type is also used to pre-filter the results returned by find.

The FindClause type lets you write filtering and recursion control expressions clearly and easily.

For example, this clause matches C source files.

 extension ==? ".c" ||? extension ==? ".h"
 

Because FindClause is a monad, you can use the usual monad machinery to, for example, lift pure functions into it.

Here's a clause that will return False for any file whose directory name contains the word "temp".

 (isInfixOf "temp") `liftM` directory
 
Synopsis
data FileInfo = FileInfo {
infoPath :: FilePath
infoDepth :: Int
infoStatus :: FileStatus
}
data FileType
= BlockDevice
| CharacterDevice
| NamedPipe
| RegularFile
| Directory
| SymbolicLink
| Socket
| Unknown
data FindClause a
type FilterPredicate = FindClause Bool
type RecursionPredicate = FindClause Bool
find :: RecursionPredicate -> FilterPredicate -> FilePath -> IO [FilePath]
fold :: RecursionPredicate -> (a -> FileInfo -> a) -> a -> FilePath -> IO a
findWithHandler :: (FilePath -> Exception -> IO [FilePath]) -> RecursionPredicate -> FilterPredicate -> FilePath -> IO [FilePath]
foldWithHandler :: (FilePath -> a -> Exception -> IO a) -> RecursionPredicate -> (a -> FileInfo -> a) -> a -> FilePath -> IO a
evalClause :: FindClause a -> FileInfo -> a
statusType :: FileStatus -> FileType
liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m c
filePath :: FindClause FilePath
fileStatus :: FindClause FileStatus
depth :: FindClause Int
fileInfo :: FindClause FileInfo
always :: FindClause Bool
extension :: FindClause FilePath
directory :: FindClause FilePath
fileName :: FindClause FilePath
fileType :: FindClause FileType
contains :: FilePath -> FindClause Bool
deviceID :: FindClause DeviceID
fileID :: FindClause FileID
fileOwner :: FindClause UserID
fileGroup :: FindClause GroupID
fileSize :: FindClause FileOffset
linkCount :: FindClause LinkCount
specialDeviceID :: FindClause DeviceID
fileMode :: FindClause FileMode
accessTime :: FindClause EpochTime
modificationTime :: FindClause EpochTime
statusChangeTime :: FindClause EpochTime
filePerms :: FindClause FileMode
anyPerms :: FileMode -> FindClause Bool
readLink :: FindClause (Maybe FilePath)
followStatus :: FindClause (Maybe FileStatus)
(~~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
(/~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
(==?) :: 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
data FileInfo
Information collected during the traversal of a directory.
Constructors
FileInfo
infoPath :: FilePathfile path
infoDepth :: Intcurrent recursion depth
infoStatus :: FileStatusstatus of file
show/hide Instances
data FileType
Constructors
BlockDevice
CharacterDevice
NamedPipe
RegularFile
Directory
SymbolicLink
Socket
Unknown
show/hide Instances
data FindClause a
Monadic container for file information, allowing for clean construction of combinators. Wraps the State monad, but doesn't allow get or put.
show/hide Instances
??? a => Functor (FindClause a)
??? a => Monad (FindClause a)
type FilterPredicate = FindClause Bool
type RecursionPredicate = FindClause Bool
Simple entry points
find
:: RecursionPredicatecontrol recursion into subdirectories
-> FilterPredicatedecide whether a file appears in the result
-> FilePathdirectory to start searching
-> IO [FilePath]files that matched the FilterPredicate
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.
fold :: RecursionPredicate -> (a -> FileInfo -> a) -> a -> FilePath -> IO a
Search a directory recursively, with recursion controlled by a RecursionPredicate. Fold over all files found. Any errors that occur are ignored, with warnings printed to stderr. The fold function is run from "left" to "right", so it should be strict in its left argument to avoid space leaks. If you need a right-to-left fold, use foldr on the result of findWithHandler instead.
More expressive entry points
findWithHandler
:: (FilePath -> Exception -> IO [FilePath])error handler
-> RecursionPredicatecontrol recursion into subdirectories
-> FilterPredicatedecide whether a file appears in the result
-> FilePathdirectory to start searching
-> IO [FilePath]files that matched the FilterPredicate
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.
foldWithHandler
:: (FilePath -> a -> Exception -> IO a)error handler
-> RecursionPredicatecontrol recursion into subdirectories
-> (a -> FileInfo -> a)function to fold with
-> aseed value for fold
-> FilePathdirectory to start searching
-> IO afinal value after folding
Search a directory recursively, with recursion controlled by a RecursionPredicate. Fold over all files found. Any errors that occur are dealt with by the given handler. The fold function is run from "left" to "right", so it should be strict in its left argument to avoid space leaks. If you need a right-to-left fold, use foldr on the result of findWithHandler instead.
Helper functions
evalClause :: FindClause a -> FileInfo -> a

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
 
statusType :: FileStatus -> FileType
Return the type of a file. This is much more useful for case analysis than the usual functions on FileStatus values.
liftOp :: Monad m => (a -> b -> c) -> m a -> b -> m c
Lift a binary operator into the FindClause monad, so that it becomes a combinator. The left hand side of the combinator should be a FindClause a, while the right remains a normal value of type a.
Combinators for controlling recursion and filtering behaviour
filePath :: FindClause FilePath
Return the name of the file being visited.
fileStatus :: FindClause FileStatus
Return the FileStatus for the current file.
depth :: FindClause Int
Return the current recursion depth.
fileInfo :: FindClause FileInfo
Return the current FileInfo.
always :: FindClause Bool
Unconditionally return True.
extension :: FindClause FilePath

Return the file name extension.

Example:

 extension "foo/bar.txt" => ".txt"
 
directory :: FindClause FilePath

Return the directory name, without the file name.

What this means in practice:

 directory "foo/bar.txt" => "foo"
 

Example in a clause:

 let hasSuffix = liftOp isSuffixOf
 in directory `hasSuffix` "tests"
 
fileName :: FindClause FilePath

Return the file name, without the directory name.

What this means in practice:

 fileName "foo/bar.txt" => "bar.txt"
 

Example:

 fileName ==? "init.c"
 
fileType :: FindClause FileType

Return the type of file currently being visited.

Example:

 fileType ==? RegularFile
 
contains :: FilePath -> FindClause Bool
Return True if the given path exists, relative to the current file. For example, if "foo" is being visited, and you call contains "bar", this combinator will return True if "foo/bar" exists.
Combinator versions of FileStatus functions from System.Posix.Files

These are simply lifted versions of the FileStatus accessor functions in the System.Posix.Files module. The definitions all have the following form:

 deviceID :: FindClause System.Posix.Types.DeviceID
 deviceID = System.Posix.Files.deviceID `liftM` fileStatus
 
deviceID :: FindClause DeviceID
fileID :: FindClause FileID
fileOwner :: FindClause UserID
fileGroup :: FindClause GroupID
fileSize :: FindClause FileOffset
linkCount :: FindClause LinkCount
specialDeviceID :: FindClause DeviceID
fileMode :: FindClause FileMode
accessTime :: FindClause EpochTime
modificationTime :: FindClause EpochTime
statusChangeTime :: FindClause EpochTime
Convenience combinators for file status
filePerms :: FindClause FileMode
Return the permission bits of the FileMode.
anyPerms :: FileMode -> FindClause Bool

Return True if any of the given permission bits is set.

Example:

 anyPerms 0444
 
Combinators that operate on symbolic links
readLink :: FindClause (Maybe FilePath)
If the current file is a symbolic link, return Just the target of the link, otherwise Nothing.
followStatus :: FindClause (Maybe FileStatus)

If the current file is a symbolic link, return Just the status of the ultimate endpoint of the link. Otherwise (including in the case of an error), return Nothing.

Example:

 statusType `liftM` followStatus ==? RegularFile
 
Common binary operators, lifted as combinators

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 (==)
(~~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
Return True if the current file's name matches the given GlobPattern.
(/~?) :: FindClause FilePath -> GlobPattern -> FindClause Bool
Return True if the current file's name does not match the given GlobPattern.
(==?) :: 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
This operator is useful to check if bits are set in a FileMode.
Combinators for gluing clauses together
(&&?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
(||?) :: FindClause Bool -> FindClause Bool -> FindClause Bool
Produced by Haddock version 0.8