Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- sourceFindFiles :: (MonadIO m, MonadSafe m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> Producer (FileEntry f, a) m ()
- find :: (MonadIO m, MonadSafe m) => FilePath -> CondT (FileEntry FilePath) m a -> Producer FilePath m ()
- findFiles :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadCatch m, MonadMask m) => FindOptions -> FilePath -> CondT (FileEntry FilePath) m a -> m ()
- findFilesIO :: IsFilePath f => FindOptions -> f -> CondT (FileEntry f) IO a -> IO ()
- findFilePaths :: (MonadIO m, MonadSafe m) => FindOptions -> FilePath -> CondT (FileEntry FilePath) m a -> Producer FilePath m ()
- data FindOptions = FindOptions {}
- defaultFindOptions :: FindOptions
- directoryFiles :: (MonadPlus m, MonadIO m) => FilePath -> TreeT m FilePath
- test :: MonadIO m => CondT (FileEntry FilePath) m () -> FilePath -> m Bool
- ltest :: MonadIO m => CondT (FileEntry FilePath) m () -> FilePath -> m Bool
- stat :: MonadIO m => CondT (FileEntry f) m FileStatus
- lstat :: MonadIO m => CondT (FileEntry f) m FileStatus
- hasStatus :: MonadIO m => (FileStatus -> Bool) -> CondT (FileEntry f) m ()
- glob :: (Monad m, IsString f, IsFilePath f, Monoid f) => String -> CondT (FileEntry f) m ()
- regex :: (Monad m, IsFilePath f) => String -> CondT (FileEntry f) m ()
- ignoreVcs :: (Monad m, IsString f, Eq f, IsFilePath f) => CondT (FileEntry f) m ()
- depth_ :: Monad m => CondT (FileEntry f) m ()
- follow_ :: Monad m => CondT (FileEntry f) m ()
- prune_ :: Monad m => CondT a m ()
- maxdepth_ :: Monad m => Int -> CondT (FileEntry f) m ()
- mindepth_ :: Monad m => Int -> CondT (FileEntry f) m ()
- ignoreErrors_ :: Monad m => CondT (FileEntry f) m ()
- noIgnoreErrors_ :: Monad m => CondT (FileEntry f) m ()
- amin_ :: MonadIO m => Int -> CondT (FileEntry f) m ()
- atime_ :: MonadIO m => Int -> CondT (FileEntry f) m ()
- anewer_ :: (MonadIO m, IsFilePath f) => f -> CondT (FileEntry f) m ()
- empty_ :: MonadIO m => CondT (FileEntry f) m ()
- executable_ :: MonadIO m => CondT (FileEntry f) m ()
- gid_ :: MonadIO m => Int -> CondT (FileEntry f) m ()
- name_ :: (Monad m, IsFilePath f, Eq f) => f -> CondT (FileEntry f) m ()
- getDepth :: Monad m => CondT (FileEntry f) m Int
- filename_ :: (Monad m, IsFilePath f) => (f -> Bool) -> CondT (FileEntry f) m ()
- pathname_ :: (Monad m, IsFilePath f) => (f -> Bool) -> CondT (FileEntry f) m ()
- getEntryPath :: (Monad m, IsFilePath f) => CondT (FileEntry f) m f
- getRawEntryPath :: Monad m => CondT (FileEntry f) m RawFilePath
- regular :: MonadIO m => CondT (FileEntry f) m ()
- directory :: MonadIO m => CondT (FileEntry f) m ()
- hasMode :: MonadIO m => FileMode -> CondT (FileEntry f) m ()
- executable :: MonadIO m => CondT (FileEntry f) m ()
- lastAccessed_ :: MonadIO m => (UTCTime -> Bool) -> CondT (FileEntry f) m ()
- lastModified_ :: MonadIO m => (UTCTime -> Bool) -> CondT (FileEntry f) m ()
- module Control.Cond
- (=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
- data FileEntry f = FileEntry {
- entryPath :: !RawFilePath
- entryDepth :: !Int
- entryFindOptions :: !FindOptions
- entryStatus :: !(Maybe FileStatus)
- class IsFilePath a where
- genericFindFiles :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadCatch m, MonadMask m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> m ()
- genericFindFilePaths :: (MonadIO m, MonadSafe m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> Producer f m ()
- genericFind :: (MonadIO m, MonadSafe m, IsFilePath f) => f -> CondT (FileEntry f) m a -> Producer f m ()
- genericTest :: (MonadIO m, IsFilePath f) => CondT (FileEntry f) m () -> f -> m Bool
- genericLtest :: (MonadIO m, IsFilePath f) => CondT (FileEntry f) m () -> f -> m Bool
Introduction
- *find-conduit** is essentially a souped version of GNU find for Haskell, using a DSL to provide both ease of us, and extensive flexbility.
In its simplest form, let's compare some uses of find to find-conduit. Bear in mind that the result of the find function is a conduit, so you're expected to either sink it to a list, or operate on the file paths as they are yielded.
Basic comparison with GNU find
A typical find command:
find src -name '*.hs' -type f -print
Would in find-conduit be:
find "src" (glob "*.hs" <> regular) $$ mapM_C (liftIO . print)
The glob
predicate matches the file basename against the globbing pattern,
while the regular
predicate matches plain files.
A more complicated example:
find . -size +100M -perm 644 -mtime 1
Now in find-conduit:
let megs = 1024 * 1024 days = 86400 now <- liftIO getCurrentTime find "." ( fileSize (> 100*megs) <> hasMode 0o644 <> lastModified (> addUTCTime now (-(1*days))) )
Appending predicates like this expressing an "and" relationship. Use <|>
to
express "or". You can also negate any predicate:
find "." (not_ (hasMode 0o644))
By default, predicates, whether matching or not, will allow recursion into
directories. In order to express that matching predicate should disallow
recursion, use prune
:
find "." (prune (depth (> 2)))
This is the same as using '-maxdepth 2' in find.
find "." (prune (filename_ (== "dist")))
This is the same as:
find . \( -name dist -prune \) -o -print
Performance
find-conduit strives to make file-finding a well performing operation. To this end, a composed Predicate will only call stat once per entry being considered; and if you prune a directory, it is not traversed at all.
By default, find
calls stat for every file before it applies the predicate,
in order to ensure that only one such call is needed. Sometimes, however, you
know just from the FilePath that you don't want to consider a certain file, or
you want to prune a directory tree.
To support these types of optimized queries, a variant of find is provided
called findWithPreFilter
. This takes two predicates: one that is applied to
only the FilePath, before stat (or lstat) is called; and one that is applied
to the full file information after the stat.
Other notes
See Cond
for more details on the Monad used to build predicates.
Finding functions
sourceFindFiles :: (MonadIO m, MonadSafe m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> Producer (FileEntry f, a) m () Source #
Find file entries in a directory tree, recursively, applying the given
recursion predicate to the search. This conduit yields pairs of type
(FileEntry f, a)
, where is the return value from the predicate at each
step.
find :: (MonadIO m, MonadSafe m) => FilePath -> CondT (FileEntry FilePath) m a -> Producer FilePath m () Source #
Calls findFilePaths
with the default set of finding options.
Equivalent to findFilePaths defaultFindOptions
.
findFiles :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadCatch m, MonadMask m) => FindOptions -> FilePath -> CondT (FileEntry FilePath) m a -> m () Source #
findFilesIO :: IsFilePath f => FindOptions -> f -> CondT (FileEntry f) IO a -> IO () Source #
Find file entries in a directory tree, recursively, applying the given
recursion predicate to the search. This conduit yields pairs of type
(FileEntry f, a)
, where is the return value from the predicate at each
step.
findFilePaths :: (MonadIO m, MonadSafe m) => FindOptions -> FilePath -> CondT (FileEntry FilePath) m a -> Producer FilePath m () Source #
data FindOptions Source #
FindOptions | |
|
directoryFiles :: (MonadPlus m, MonadIO m) => FilePath -> TreeT m FilePath Source #
Return all files within a directory tree, hierarchically.
test :: MonadIO m => CondT (FileEntry FilePath) m () -> FilePath -> m Bool Source #
Test a file path using the same type of predicate that is accepted by
findFiles
.
ltest :: MonadIO m => CondT (FileEntry FilePath) m () -> FilePath -> m Bool Source #
Test a file path using the same type of predicate that is accepted by
findFiles
, but do not follow symlinks.
File path predicates
glob :: (Monad m, IsString f, IsFilePath f, Monoid f) => String -> CondT (FileEntry f) m () Source #
Find every entry whose filename part matching the given filename globbing
expression. For example: glob "*.hs"
.
ignoreVcs :: (Monad m, IsString f, Eq f, IsFilePath f) => CondT (FileEntry f) m () Source #
Return all entries, except for those within version-control metadata directories (and not including the version control directory itself either).
GNU find compatibility predicates
getEntryPath :: (Monad m, IsFilePath f) => CondT (FileEntry f) m f Source #
getRawEntryPath :: Monad m => CondT (FileEntry f) m RawFilePath Source #
File entry predicates (uses stat information)
Predicate combinators
module Control.Cond
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target #
Types and type classes
FileEntry | |
|
class IsFilePath a where Source #
getRawFilePath :: a -> RawFilePath Source #
getFilePath :: a -> FilePath Source #
fromRawFilePath :: RawFilePath -> a Source #
fromFilePath :: FilePath -> a Source #
fromTextPath :: Text -> a Source #
Instances
IsFilePath ByteString Source # | |
Defined in Pipes.Files.Types getRawFilePath :: ByteString -> RawFilePath Source # getFilePath :: ByteString -> FilePath Source # fromRawFilePath :: RawFilePath -> ByteString Source # fromFilePath :: FilePath -> ByteString Source # fromTextPath :: Text -> ByteString Source # | |
a ~ Char => IsFilePath [a] Source # | |
Defined in Pipes.Files.Types getRawFilePath :: [a] -> RawFilePath Source # getFilePath :: [a] -> FilePath Source # fromRawFilePath :: RawFilePath -> [a] Source # fromFilePath :: FilePath -> [a] Source # fromTextPath :: Text -> [a] Source # |
Helper functions for library writers
genericFindFiles :: (MonadIO m, MonadBaseControl IO m, MonadThrow m, MonadCatch m, MonadMask m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> m () Source #
genericFindFilePaths :: (MonadIO m, MonadSafe m, IsFilePath f) => FindOptions -> f -> CondT (FileEntry f) m a -> Producer f m () Source #
genericFind :: (MonadIO m, MonadSafe m, IsFilePath f) => f -> CondT (FileEntry f) m a -> Producer f m () Source #
Calls findFilePaths
with the default set of finding options.
Equivalent to findFilePaths defaultFindOptions
.
genericTest :: (MonadIO m, IsFilePath f) => CondT (FileEntry f) m () -> f -> m Bool Source #
Test a file path using the same type of predicate that is accepted by
findFiles
.
genericLtest :: (MonadIO m, IsFilePath f) => CondT (FileEntry f) m () -> f -> m Bool Source #
Test a file path using the same type of predicate that is accepted by
findFiles
, but do not follow symlinks.