Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type TreeT m = CofreeT Maybe (ListT m)
- selectEach :: Monad m => m [a] -> ListT m a
- directoryFiles :: MonadIO m => FilePath -> TreeT m FilePath
- descend :: Monad m => TreeT m a -> ListT m (a, Maybe (TreeT m a))
- walk :: Monad m => TreeT m a -> ListT m a
- winnow :: Monad m => TreeT m a -> CondT a m () -> TreeT m a
Documentation
selectEach :: Monad m => m [a] -> ListT m a Source
Turn a generated list into a ListT
.
directoryFiles :: MonadIO m => FilePath -> TreeT m FilePath Source
Return all files within a directory tree, hierarchically.
descend :: Monad m => TreeT m a -> ListT m (a, Maybe (TreeT m a)) Source
Descend one level into a TreeT
, yielding a list of values and their
possible associated trees.
winnow :: Monad m => TreeT m a -> CondT a m () -> TreeT m a Source
Given a TreeT
, produce another TreeT
which yields only those elements
(and sub-trees) matching the given monadic conditional. This conditional
(see CondT
) can choose both elements and points of
recursion, making it capable of expressing any tree traversal in the form
of a predicate DSL. This differs from an expression-based traversal, like
XPath or Lens, in that effects in m
may be used to guide selection.
For example, to print all Haskell files under the current directory:
let files = winnow (directoryFiles ".") $ do path <- query liftIO $ putStrLn $ "Considering " ++ path when (path`elem
` ["./
.git", "./
dist", "./
result"]) prune -- ignore these, and don't recurse into them guard_ (".hs"`isInfixOf
`) -- implicitly referencespath
runEffect $ for (enumerate (walk files)) $ liftIO . print