Safe Haskell | None |
---|---|
Language | Haskell2010 |
A monadic interface to Tree mutation. The main idea is to
simulate IO-ish manipulation of real filesystem (that's the state part of
the monad), and to keep memory usage down by reasonably often dumping the
intermediate data to disk and forgetting it. The monad interface itself is
generic, and a number of actual implementations can be used. This module
provides just virtualTreeIO
that never writes any changes, but may trigger
filesystem reads as appropriate.
Synopsis
- type TreeMonad m = RWST (TreeEnv m) () (TreeState m) m
- data TreeState m
- runTreeMonad :: Monad m => TreeMonad m a -> Tree m -> (TreeItem m -> m Hash) -> (AnchoredPath -> TreeItem m -> TreeMonad m (TreeItem m)) -> m (a, Tree m)
- virtualTreeMonad :: Monad m => TreeMonad m a -> Tree m -> m (a, Tree m)
- type TreeIO = TreeMonad IO
- virtualTreeIO :: TreeIO a -> Tree IO -> IO (a, Tree IO)
- readFile :: Monad m => AnchoredPath -> TreeMonad m ByteString
- exists :: Monad m => AnchoredPath -> TreeMonad m Bool
- directoryExists :: Monad m => AnchoredPath -> TreeMonad m Bool
- fileExists :: Monad m => AnchoredPath -> TreeMonad m Bool
- writeFile :: Monad m => AnchoredPath -> ByteString -> TreeMonad m ()
- createDirectory :: Monad m => AnchoredPath -> TreeMonad m ()
- unlink :: Monad m => AnchoredPath -> TreeMonad m ()
- rename :: Monad m => AnchoredPath -> AnchoredPath -> TreeMonad m ()
- copy :: Monad m => AnchoredPath -> AnchoredPath -> TreeMonad m ()
- findM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (TreeItem m))
- findFileM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (Blob m))
- findTreeM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (Tree m))
TreeMonad
type TreeMonad m = RWST (TreeEnv m) () (TreeState m) m Source #
A monad transformer that adds state of type TreeState
and an environment
of type AnchoredPath
(for the current directory).
Instances
runTreeMonad :: Monad m => TreeMonad m a -> Tree m -> (TreeItem m -> m Hash) -> (AnchoredPath -> TreeItem m -> TreeMonad m (TreeItem m)) -> m (a, Tree m) Source #
virtualTreeMonad :: Monad m => TreeMonad m a -> Tree m -> m (a, Tree m) Source #
Run a TreeMonad
action without storing any changes. This is useful for
running monadic tree mutations for obtaining the resulting Tree
(as opposed
to their effect of writing a modified tree to disk). The actions can do both
read and write -- reads are passed through to the actual filesystem, but the
writes are held in memory in the form of a modified Tree
.
Specializing to IO
Read actions
readFile :: Monad m => AnchoredPath -> TreeMonad m ByteString Source #
Grab content of a file in the current Tree at the given path.
exists :: Monad m => AnchoredPath -> TreeMonad m Bool Source #
Check for existence of a node (file or directory, doesn't matter).
directoryExists :: Monad m => AnchoredPath -> TreeMonad m Bool Source #
Check for existence of a directory.
fileExists :: Monad m => AnchoredPath -> TreeMonad m Bool Source #
Check for existence of a file.
Write actions
writeFile :: Monad m => AnchoredPath -> ByteString -> TreeMonad m () Source #
Change content of a file at a given path. The change will be eventually flushed to disk, but might be buffered for some time.
createDirectory :: Monad m => AnchoredPath -> TreeMonad m () Source #
Create a directory.
rename :: Monad m => AnchoredPath -> AnchoredPath -> TreeMonad m () Source #
Rename the item at a path.
copy :: Monad m => AnchoredPath -> AnchoredPath -> TreeMonad m () Source #
Copy an item from some path to another path.