hashed-storage-0.3: Hashed file storage support code.Source codeContentsIndex
Storage.Hashed.Tree
Contents
Unfolding stubbed (lazy) Trees.
Tree access and lookup.
Files (Blobs).
Manipulating trees.
Description
The abstract representation of a Tree and useful abstract utilities to handle those.
Synopsis
data Tree
data Blob = Blob !(IO ByteString) !(Maybe Hash)
data TreeItem
= File !Blob
| SubTree !Tree
| Stub !(IO Tree) !(Maybe Hash)
data ItemType
= BlobType
| TreeType
newtype Hash = Hash (Maybe Int64, ByteString)
makeTree :: [(Name, TreeItem)] -> Tree
makeTreeWithHash :: [(Name, TreeItem)] -> Hash -> Tree
darcsTreeHash :: Tree -> Hash
darcsFormatDir :: Tree -> ByteString
emptyTree :: Tree
emptyBlob :: Blob
unfold :: Tree -> IO Tree
unfoldPath :: Tree -> AnchoredPath -> IO Tree
items :: Tree -> Map Name TreeItem
list :: Tree -> [(AnchoredPath, TreeItem)]
listImmediate :: Tree -> [(Name, TreeItem)]
treeHash :: Tree -> Maybe Hash
lookup :: Tree -> Name -> Maybe TreeItem
find :: Tree -> AnchoredPath -> Maybe TreeItem
findFile :: Tree -> AnchoredPath -> Maybe Blob
findTree :: Tree -> AnchoredPath -> Maybe Tree
itemHash :: TreeItem -> Maybe Hash
itemType :: TreeItem -> ItemType
zipCommonFiles :: (AnchoredPath -> Blob -> Blob -> a) -> Tree -> Tree -> [a]
zipFiles :: (AnchoredPath -> Maybe Blob -> Maybe Blob -> a) -> Tree -> Tree -> [a]
zipTrees :: (AnchoredPath -> Maybe TreeItem -> Maybe TreeItem -> a) -> Tree -> Tree -> [a]
diffTrees :: Tree -> Tree -> IO (Tree, Tree)
read :: Blob -> IO ByteString
finish :: Tree -> Tree -> IO Tree
filter :: (AnchoredPath -> TreeItem -> Bool) -> Tree -> Tree
restrict :: Tree -> Tree -> Tree
modifyTree :: Tree -> AnchoredPath -> Maybe TreeItem -> Tree
Documentation
data Tree Source

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 unfold on it, eg.:

 tree <- readDarcsPristine "." >>= unfold

When a Tree is unfolded, 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).

data Blob Source
Constructors
Blob !(IO ByteString) !(Maybe Hash)
data TreeItem Source
Constructors
File !Blob
SubTree !Tree
Stub !(IO Tree) !(Maybe Hash)
data ItemType Source
Constructors
BlobType
TreeType
show/hide Instances
newtype Hash Source
Constructors
Hash (Maybe Int64, ByteString)
show/hide Instances
makeTree :: [(Name, TreeItem)] -> TreeSource
makeTreeWithHash :: [(Name, TreeItem)] -> Hash -> TreeSource
darcsTreeHash :: Tree -> HashSource
Compute a darcs-compatible hash value for a tree-like structure.
darcsFormatDir :: Tree -> ByteStringSource
emptyTree :: TreeSource
emptyBlob :: BlobSource
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. unfold will produce an unstubbed Tree.
unfold :: Tree -> IO TreeSource
Unfold a stubbed Tree into a one with no stubs in it. You might want to filter the tree before unfolding to save IO.
unfoldPath :: Tree -> AnchoredPath -> IO TreeSource
Unfold a path in a (stubbed) Tree, such that the leaf node of the path is reachable without crossing any stubs.
Tree access and lookup.
items :: Tree -> Map Name TreeItemSource
list :: Tree -> [(AnchoredPath, TreeItem)]Source
List all contents of a Tree.
listImmediate :: Tree -> [(Name, TreeItem)]Source
treeHash :: Tree -> Maybe HashSource
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 -> Name -> Maybe TreeItemSource
Look up a Tree item (an immediate subtree or blob).
find :: Tree -> AnchoredPath -> Maybe TreeItemSource
Find a TreeItem by its path. Gives Nothing if the path is invalid.
findFile :: Tree -> AnchoredPath -> Maybe BlobSource
Find a Blob by its path. Gives Nothing if the path is invalid, or does not point to a Blob.
findTree :: Tree -> AnchoredPath -> Maybe TreeSource
Find a Tree by its path. Gives Nothing if the path is invalid, or does not point to a Tree.
itemHash :: TreeItem -> Maybe HashSource
Get a hash of a TreeItem. May be Nothing.
itemType :: TreeItem -> ItemTypeSource
zipCommonFiles :: (AnchoredPath -> Blob -> Blob -> a) -> Tree -> Tree -> [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 unfold any stubs.
zipFiles :: (AnchoredPath -> Maybe Blob -> Maybe Blob -> a) -> Tree -> Tree -> [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 unfold any stubs.
zipTrees :: (AnchoredPath -> Maybe TreeItem -> Maybe TreeItem -> a) -> Tree -> Tree -> [a]Source
diffTrees :: Tree -> Tree -> IO (Tree, Tree)Source
Cautiously extracts differing subtrees from a pair of Trees. It will never do any unneccessary unfolding. 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 unfolded. It might be advantageous to feed the result into zipFiles.
Files (Blobs).
read :: Blob -> IO ByteStringSource
Read a Blob into a Lazy ByteString. Might be backed by an mmap, use with care.
Manipulating trees.
finish :: Tree -> Tree -> IO TreeSource
When implementing a Tree that has complex unfolding semantics, the finish IO action lets you do arbitrary IO transform on the Tree after it is unfolded but before it is given to the user by unfold. (Used to implement Index updates, eg.)
filter :: (AnchoredPath -> TreeItem -> Bool) -> Tree -> TreeSource
Given a predicate of the form AnchoredPath -> TreeItem -> Bool, and a Tree, produce a Tree that only has items for which the predicate returned True. The tree might contain stubs. When unfolded, these will be subject to filtering as well.
restrict :: Tree -> Tree -> TreeSource
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.
modifyTree :: Tree -> AnchoredPath -> Maybe TreeItem -> TreeSource
Produced by Haddock version 2.4.2