| Safe Haskell | None |
|---|
Data.Conduit.Find
- data FileEntry = FileEntry {}
- type Predicate m a = Looped m a a
- class HasFilePath a where
- getFilePath :: a -> FilePath
- sourceFileEntries :: MonadResource m => Looped m FilePath FileEntry -> FilePath -> Producer m FileEntry
- matchAll :: Monad m => Predicate m a
- ignoreVcs :: (MonadIO m, HasFilePath e) => Predicate m e
- regexMatcher :: (Monad m, HasFilePath e) => (FilePath -> FilePath) -> Text -> Predicate m e
- regex :: (Monad m, HasFilePath e) => Text -> Predicate m e
- glob :: (Monad m, HasFilePath e) => Text -> Predicate m e
- stat :: MonadIO m => Looped m FilePath FileEntry
- lstat :: MonadIO m => Looped m FilePath FileEntry
- getPath :: MonadIO m => Looped m FileEntry FilePath
- regular :: Monad m => Predicate m FileEntry
- executable :: Monad m => Predicate m FileEntry
- prune :: (Monad m, HasFilePath e) => FilePath -> Predicate m e
- test :: MonadIO m => Predicate m FileEntry -> FilePath -> m Bool
- find :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FilePath
- find' :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FileEntry
- lfind :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FilePath
- lfind' :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FileEntry
- findWithPreFilter :: (MonadIO m, MonadResource m) => FilePath -> Bool -> Predicate m FilePath -> Predicate m FileEntry -> Producer m FileEntry
- readPaths :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FilePath -> Producer m FilePath
- or_ :: MonadIO m => Looped m a b -> Looped m a b -> Looped m a b
- and_ :: MonadIO m => Looped m a b -> Looped m a b -> Looped m a b
- not_ :: MonadIO m => Looped m a a -> Looped m a a
Documentation
Constructors
| FileEntry | |
Fields | |
Instances
sourceFileEntries :: MonadResource m => Looped m FilePath FileEntry -> FilePath -> Producer m FileEntrySource
Walk through the entries of a directory tree, allowing the user to
specify a Predicate which may decides not only which entries to yield
from the conduit, but also which directories to follow, and how to
recurse into that directory by permitting the use of a subsequent
Predicate.
Note that the followSymlinks parameter to this function has a different
meaning than it does for sourceDirectoryDeep: if True, symlinks are
never passed to the predicate, only what they point to; if False,
symlinks are never read at all. For sourceDirectoryDeep, if
followSymlinks is False it only prevents directory symlinks from
being read.
matchAll :: Monad m => Predicate m aSource
Return all entries. This is the same as sourceDirectoryDeep, except
that the FileStatus structure for each entry is also provided. As a
result, only one stat call is ever made per entry, compared to two per
directory in the current version of sourceDirectoryDeep.
ignoreVcs :: (MonadIO m, HasFilePath e) => Predicate m eSource
Return all entries, except for those within version-control metadata directories (and not including the version control directory itself either).
Arguments
| :: (Monad m, HasFilePath e) | |
| => (FilePath -> FilePath) | Function that specifies which part of the pathname to match against. Use this to match against only filenames, or to relativize the path against the search root before comparing. |
| -> Text | The regular expression search pattern. |
| -> Predicate m e |
The regexMatcher predicate builder matches some part of every path
against a given regex. Use the simpler regex if you just want to apply
a regex to every file name.
regex :: (Monad m, HasFilePath e) => Text -> Predicate m eSource
Find every entry whose filename part matching the given regular expression.
glob :: (Monad m, HasFilePath e) => Text -> Predicate m eSource
Find every entry whose filename part matching the given filename globbing
expression. For example: glob *.hs.
executable :: Monad m => Predicate m FileEntrySource
find :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FilePathSource
find' :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FileEntrySource
lfind :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FilePathSource
lfind' :: (MonadIO m, MonadResource m) => FilePath -> Predicate m FileEntry -> Producer m FileEntrySource
findWithPreFilter :: (MonadIO m, MonadResource m) => FilePath -> Bool -> Predicate m FilePath -> Predicate m FileEntry -> Producer m FileEntrySource
Run a find, but using a pre-pass filter on the FilePaths, to eliminates files from consideration early and avoid calling stat on them.