Safe Haskell | None |
---|---|
Language | Haskell2010 |
The abstract representation of a Tree and useful abstract utilities to handle those.
- data Tree m
- data Blob m = Blob !(m ByteString) !Hash
- data TreeItem m
- data ItemType
- data Hash
- = SHA256 !ByteString
- | NoHash
- makeTree :: [(Name, TreeItem m)] -> Tree m
- makeTreeWithHash :: [(Name, TreeItem m)] -> Hash -> Tree m
- emptyTree :: Tree m
- emptyBlob :: Monad m => Blob m
- makeBlob :: Monad m => ByteString -> Blob m
- makeBlobBS :: Monad m => ByteString -> Blob m
- expandUpdate :: Monad m => (AnchoredPath -> Tree m -> m (Tree m)) -> Tree m -> m (Tree m)
- expand :: Monad m => Tree m -> m (Tree m)
- expandPath :: Monad m => Tree m -> AnchoredPath -> m (Tree m)
- checkExpand :: (TreeItem IO -> IO Hash) -> Tree IO -> IO (Either [(AnchoredPath, Hash, Maybe Hash)] (Tree IO))
- items :: Tree m -> Map Name (TreeItem m)
- list :: Tree m -> [(AnchoredPath, TreeItem m)]
- listImmediate :: Tree m -> [(Name, TreeItem m)]
- treeHash :: Tree m -> Hash
- lookup :: Tree m -> Name -> Maybe (TreeItem m)
- find :: Tree m -> AnchoredPath -> Maybe (TreeItem m)
- findFile :: Tree m -> AnchoredPath -> Maybe (Blob m)
- findTree :: Tree m -> AnchoredPath -> Maybe (Tree m)
- itemHash :: TreeItem m -> Hash
- itemType :: TreeItem m -> ItemType
- zipCommonFiles :: (AnchoredPath -> Blob m -> Blob m -> a) -> Tree m -> Tree m -> [a]
- zipFiles :: (AnchoredPath -> Maybe (Blob m) -> Maybe (Blob m) -> a) -> Tree m -> Tree m -> [a]
- zipTrees :: (AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m) -> a) -> Tree m -> Tree m -> [a]
- diffTrees :: forall m. Monad m => Tree m -> Tree m -> m (Tree m, Tree m)
- readBlob :: Blob m -> m ByteString
- class Monad m => FilterTree a m where
- restrict :: FilterTree t m => Tree n -> t m -> t m
- modifyTree :: Monad m => Tree m -> AnchoredPath -> Maybe (TreeItem m) -> Tree m
- updateTree :: Monad m => (TreeItem m -> m (TreeItem m)) -> Tree m -> m (Tree m)
- partiallyUpdateTree :: Monad m => (TreeItem m -> m (TreeItem m)) -> (AnchoredPath -> TreeItem m -> Bool) -> Tree m -> m (Tree m)
- updateSubtrees :: (Tree m -> Tree m) -> Tree m -> Tree m
- overlay :: Monad m => Tree m -> Tree m -> Tree m
- addMissingHashes :: Monad m => (TreeItem m -> m Hash) -> Tree m -> m (Tree m)
Documentation
Abstraction of a filesystem tree. Please note that the Tree returned by the respective read operations will have TreeStub items in it. To obtain a Tree without such stubs, call expand on it, eg.:
tree <- readDarcsPristine "." >>= expand
When a Tree is expanded, it becomes "final". All stubs are forced and the Tree can be traversed purely. Access to actual file contents stays in IO though.
A Tree may have a Hash associated with it. A pair of Tree's is identical whenever their hashes are (the reverse need not hold, since not all Trees come equipped with a hash).
ApplyMonadState Tree Source # | |
ToTree Tree Source # | |
Monad m => FilterTree Tree m Source # | |
ApplyMonad Tree DefaultIO Source # | |
(Functor m, Monad m) => ApplyMonadTrans Tree m Source # | |
(Functor m, Monad m) => ApplyMonad Tree (TreeMonad m) Source # | |
type ApplyMonadStateOperations Tree Source # | |
type ApplyMonadOver Tree m Source # | |
makeBlobBS :: Monad m => ByteString -> Blob m Source #
Unfolding stubbed (lazy) Trees.
By default, Tree obtained by a read function is stubbed: it will
contain Stub items that need to be executed in order to access the
respective subtrees. expand
will produce an unstubbed Tree.
expandUpdate :: Monad m => (AnchoredPath -> Tree m -> m (Tree m)) -> Tree m -> m (Tree m) Source #
expand :: Monad m => Tree m -> m (Tree m) Source #
Expand a stubbed Tree into a one with no stubs in it. You might want to filter the tree before expanding to save IO. This is the basic implementation, which may be overriden by some Tree instances (this is especially true of the Index case).
expandPath :: Monad m => Tree m -> AnchoredPath -> m (Tree m) Source #
Unfold a path in a (stubbed) Tree, such that the leaf node of the path is reachable without crossing any stubs. Moreover, the leaf ought not be a Stub in the resulting Tree. A non-existent path is expanded as far as it can be.
checkExpand :: (TreeItem IO -> IO Hash) -> Tree IO -> IO (Either [(AnchoredPath, Hash, Maybe Hash)] (Tree IO)) Source #
Check the disk version of a Tree: expands it, and checks each hash. Returns either the expanded tree or a list of AnchoredPaths where there are problems. The first argument is the hashing function used to create the tree.
Tree access and lookup.
treeHash :: Tree m -> Hash Source #
Get hash of a Tree. This is guaranteed to uniquely identify the Tree (including any blob content), as far as cryptographic hashes are concerned. Sha256 is recommended.
lookup :: Tree m -> Name -> Maybe (TreeItem m) Source #
Look up a Tree
item (an immediate subtree or blob).
zipCommonFiles :: (AnchoredPath -> Blob m -> Blob m -> a) -> Tree m -> Tree m -> [a] Source #
For every pair of corresponding blobs from the two supplied trees, evaluate the supplied function and accumulate the results in a list. Hint: to get IO actions through, just use sequence on the resulting list. NB. This won't expand any stubs.
zipFiles :: (AnchoredPath -> Maybe (Blob m) -> Maybe (Blob m) -> a) -> Tree m -> Tree m -> [a] Source #
For each file in each of the two supplied trees, evaluate the supplied function (supplying the corresponding file from the other tree, or Nothing) and accumulate the results in a list. Hint: to get IO actions through, just use sequence on the resulting list. NB. This won't expand any stubs.
zipTrees :: (AnchoredPath -> Maybe (TreeItem m) -> Maybe (TreeItem m) -> a) -> Tree m -> Tree m -> [a] Source #
diffTrees :: forall m. Monad m => Tree m -> Tree m -> m (Tree m, Tree m) Source #
Cautiously extracts differing subtrees from a pair of Trees. It will never
do any unneccessary expanding. Tree hashes are used to cut the comparison as
high up the Tree branches as possible. The result is a pair of trees that do
not share any identical subtrees. They are derived from the first and second
parameters respectively and they are always fully expanded. It might be
advantageous to feed the result into zipFiles
or zipTrees
.
Files (Blobs).
readBlob :: Blob m -> m ByteString Source #
Read a Blob into a Lazy ByteString. Might be backed by an mmap, use with care.
Filtering trees.
class Monad m => FilterTree a m where Source #
filter :: (AnchoredPath -> TreeItem m -> Bool) -> a m -> a m Source #
Given pred tree
, produce a Tree
that only has items for which
pred
returns True
.
The tree might contain stubs. When expanded, these will be subject to
filtering as well.
Monad m => FilterTree Tree m Source # | |
restrict :: FilterTree t m => Tree n -> t m -> t m Source #
Given two Trees, a guide
and a tree
, produces a new Tree that is a
identical to tree
, but only has those items that are present in both
tree
and guide
. The guide
Tree may not contain any stubs.
Manipulating trees.
modifyTree :: Monad m => Tree m -> AnchoredPath -> Maybe (TreeItem m) -> Tree m Source #
Modify a Tree (by replacing, or removing or adding items).
updateTree :: Monad m => (TreeItem m -> m (TreeItem m)) -> Tree m -> m (Tree m) Source #
Does not expand the tree.
partiallyUpdateTree :: Monad m => (TreeItem m -> m (TreeItem m)) -> (AnchoredPath -> TreeItem m -> Bool) -> Tree m -> m (Tree m) Source #
Does not expand the tree.
overlay :: Monad m => Tree m -> Tree m -> Tree m Source #
Lay one tree over another. The resulting Tree will look like the base (1st parameter) Tree, although any items also present in the overlay Tree will be taken from the overlay. It is not allowed to overlay a different kind of an object, nor it is allowed for the overlay to add new objects to base. This means that the overlay Tree should be a subset of the base Tree (although any extraneous items will be ignored by the implementation).