tahoe-chk-0.2.0.0: The Tahoe-LAFS' Content-Hash-Key (CHK) cryptographic protocol.
Safe HaskellNone
LanguageHaskell2010

Tahoe.CHK.Merkle

Synopsis

Documentation

data MerkleTree value hash Source #

A Merkle tree parameterized on a value type and hash algorithm. The value type is phantom and is intended to help avoid mixing up opaque hashes from Merkle trees used for different purposes.

Constructors

MerkleLeaf (Digest' hash) 
MerkleNode (Digest' hash) (MerkleTree value hash) (MerkleTree value hash) 

Instances

Instances details
Eq (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Methods

(==) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

(/=) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

Ord (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Methods

compare :: MerkleTree value hash -> MerkleTree value hash -> Ordering #

(<) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

(<=) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

(>) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

(>=) :: MerkleTree value hash -> MerkleTree value hash -> Bool #

max :: MerkleTree value hash -> MerkleTree value hash -> MerkleTree value hash #

min :: MerkleTree value hash -> MerkleTree value hash -> MerkleTree value hash #

HashAlgorithm hash => Show (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Methods

showsPrec :: Int -> MerkleTree value hash -> ShowS #

show :: MerkleTree value hash -> String #

showList :: [MerkleTree value hash] -> ShowS #

Generic (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Associated Types

type Rep (MerkleTree value hash) :: Type -> Type #

Methods

from :: MerkleTree value hash -> Rep (MerkleTree value hash) x #

to :: Rep (MerkleTree value hash) x -> MerkleTree value hash #

(Show hash, HashAlgorithm hash) => Binary (MerkleTree v hash) Source #

Serialize a MerkleTree to bytes by concatenating all of the leaf hashes left to right.

This serialization includes no framing so the only thing we can do is consume all available input. Use this instance with isolate and bring your own framing mechanism to determine how many bytes to process.

Instance details

Defined in Tahoe.CHK.Merkle

Methods

put :: MerkleTree v hash -> Put #

get :: Get (MerkleTree v hash) #

putList :: [MerkleTree v hash] -> Put #

ToExpr (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Methods

toExpr :: MerkleTree value hash -> Expr #

listToExpr :: [MerkleTree value hash] -> Expr #

type Rep (MerkleTree value hash) Source # 
Instance details

Defined in Tahoe.CHK.Merkle

data Direction Source #

Represent a direction to take when walking down a binary tree.

Constructors

TurnLeft 
TurnRight 

Instances

Instances details
Eq Direction Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Ord Direction Source # 
Instance details

Defined in Tahoe.CHK.Merkle

Show Direction Source # 
Instance details

Defined in Tahoe.CHK.Merkle

leafNumberToNode :: MerkleTree v a -> Int -> Maybe (MerkleTree v a) Source #

Get a leaf node by its leaf number, if possible. Leaf numbers are zero indexed and identify leaves of a tree from left to right.

leafNumberToNodeNumber :: MerkleTree v a -> Int -> Int Source #

Translate a leaf number to a node number. Leaf numbers are zero indexed and identify leaves of a tree from left to right. Node numbers are one indexed and identify nodes of a tree from top to bottom, left to right.

breadthFirstList :: forall v a. MerkleTree v a -> [Digest' a] Source #

merklePathLengthForSize :: Int -> Int Source #

Compute the length of a merkle path through a tree of the given height.

heightForLeafCount :: Integral n => n -> Int Source #

Compute the minimum height for a tree that can hold the given number of leaves.

makeTree :: forall hash value. HashAlgorithm hash => [Digest' hash] -> Maybe (MerkleTree value hash) Source #

makeTreePartial :: HashAlgorithm hash => [Digest' hash] -> MerkleTree value hash Source #

merkleProof :: MerkleTree v a -> Int -> Maybe [(Int, Digest' a)] Source #

Return a list of tuples of node numbers and corresponding merkle hashes. The node numbers correspond to a numbering of the nodes in the tree where the root node is numbered 1, each node's left child is the node's number times two, and the node's right child is the node's number times two plus one.

checkMerkleProof Source #

Arguments

:: forall n hash. (Integral n, HashAlgorithm hash) 
=> [(n, Digest' hash)]

The proof to check.

-> Digest' hash

The root hash of the merkle tree against which to check the proof.

-> Digest' hash

The leaf hash against which to check the proof.

-> Bool

True if the proof checks out, False otherwise.

Check a merkle proof for validity. The proof is valid if it represents the correct hash chain from the given leaf to the given root.

neededHashes :: MerkleTree v a -> Int -> Maybe [(Int, Digest' a)] Source #

Get a merkle proof but re-number the node numbers to be zero-indexed instead of one-indexed.

firstLeafNum :: MerkleTree v a -> Int Source #

Determine the smallest index into the breadth first list for the given tree where a leaf may be found.

size :: MerkleTree v a -> Int Source #

Count the number of nodes in a tree.

height :: MerkleTree v a -> Int Source #

Measure the height of a tree.

mapTree :: (MerkleTree v a -> b) -> MerkleTree v a -> [b] Source #

merklePath :: Int -> Int -> [Direction] Source #

Compute the path to a leaf from the root of a merkle tree of a certain height.

leafHashes :: MerkleTree v a -> [Digest' a] Source #

Get a list of all of the leaf hashes of a tree from left to right.

treeFromRows Source #

Arguments

:: (Show hash, HashAlgorithm hash) 
=> [MerkleTree value hash]

Some children to attach to a list of nodes representing the next shallowest level of the tree.

-> [[Digest' hash]]

The values of the nodes to create at the next shallowest level of the tree.

-> [MerkleTree value hash]

The nodes forming the shallowest level of the tree. If we built a full tree, there will be exactly one node here.

Given some children

buildTreeOutOfAllTheNodes :: (Show hash, HashAlgorithm hash) => [Digest' hash] -> Maybe (MerkleTree value hash) Source #

Make a merkle tree out of a flat list of all nodes (start from root, then first two children, etc .. [0, 1, 2] is a two-layer tree, [0, 1, 2, 3, 4, 5, 6] is three-layer, etc

dumpTree :: HashAlgorithm hash => MerkleTree value hash -> [Text] Source #