Safe Haskell | None |
---|
- data FileEntry = FileEntry {
- entryInfo :: FileInfo
- entryStatus :: FileStatus
- type Predicate m a = Looped m a a
- class HasFileInfo a where
- getFileInfo :: a -> FileInfo
- entryPath :: HasFileInfo a => a -> FilePath
- matchAll :: Monad m => Predicate m a
- ignoreVcs :: (MonadIO m, HasFileInfo e) => Predicate m e
- regexMatcher :: (Monad m, HasFileInfo e) => (FilePath -> FilePath) -> Text -> Predicate m e
- regex :: (Monad m, HasFileInfo e) => Text -> Predicate m e
- glob :: (Monad m, HasFileInfo e) => Text -> Predicate m e
- stat :: MonadIO m => Looped m FileInfo FileEntry
- lstat :: MonadIO m => Looped m FileInfo FileEntry
- getPath :: MonadIO m => Looped m FileEntry FilePath
- regular :: Monad m => Predicate m FileEntry
- executable :: Monad m => Predicate m FileEntry
- filename_ :: (Monad m, HasFileInfo e) => FilePath -> Predicate m e
- depth :: (Monad m, HasFileInfo e) => (Int -> Bool) -> Predicate m e
- withPath :: HasFileInfo a => Monad m => (FilePath -> m Bool) -> Predicate m a
- withStatus :: Monad m => (FileStatus -> m Bool) -> Predicate m FileEntry
- prune :: MonadIO m => Looped m a a -> Looped m a a
- 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 FileInfo -> 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
FileEntry | |
|
entryPath :: HasFileInfo a => a -> FilePathSource
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, HasFileInfo e) => Predicate m eSource
Return all entries, except for those within version-control metadata directories (and not including the version control directory itself either).
:: (Monad m, HasFileInfo 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, HasFileInfo e) => Text -> Predicate m eSource
Find every entry whose filename part matching the given regular expression.
glob :: (Monad m, HasFileInfo 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
withStatus :: Monad m => (FileStatus -> m Bool) -> 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 FileInfo -> Predicate m FileEntry -> Producer m FileEntrySource