darcs-2.16.4: a distributed, interactive, smart revision control system
Safe HaskellNone
LanguageHaskell2010

Darcs.Util.Tree.Monad

Description

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

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).

data TreeState m Source #

Internal state of the TreeMonad. Keeps track of the current Tree content and unsync'd changes.

Instances

Instances details
Monad m => ApplyMonad Tree (TreeMonad m) Source # 
Instance details

Defined in Darcs.Patch.ApplyMonad

Associated Types

type ApplyMonadBase (TreeMonad m) :: Type -> Type Source #

Monad m => MonadProgress (TreeMonad m) Source # 
Instance details

Defined in Darcs.Patch.MonadProgress

Monad m => ApplyMonadTree (TreeMonad m) Source # 
Instance details

Defined in Darcs.Patch.ApplyMonad

type ApplyMonadBase (TreeMonad m) Source # 
Instance details

Defined in Darcs.Patch.ApplyMonad

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

type TreeIO = TreeMonad IO Source #

TreeMonad specialized to IO

virtualTreeIO :: TreeIO a -> Tree IO -> IO (a, Tree IO) Source #

virtualTreeMonad specialized 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.

unlink :: Monad m => AnchoredPath -> TreeMonad m () Source #

Remove the item at a path.

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.

Other actions

findM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (TreeItem m)) Source #

findFileM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (Blob m)) Source #

findTreeM :: Monad m => Tree m -> AnchoredPath -> m (Maybe (Tree m)) Source #