merkle-log-0.1.0.0: Merkle Tree Logs

CopyrightCopyright © 2019 Kadena LLC.
LicenseMIT
MaintainerLars Kuhtz <lars@kadena.io>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.MerkleLog

Contents

Description

Merkle Logs are a append-only data structure. The tree layout in this implementation of Merkle trees is based on the description of Merkle trees in RFC 6962. With this tree layout extending a Merkle tree requires chaining a logarithmic number of nodes at the end of the tree. Unlike RFC 6962 the Merkle trees in this module support the creation of unbalanced MerkleTrees by nesting sub-trees as leafs of Merkle trees. Also, unlike RFC 6962 this module generates fully self-contained inclusion proofs that don't rely on the client being aware of the balancing of the Merkle Tree that was used to generate the proof.

The API requires the usage of type applications which can be enabled with the following pragma.

{-# LANGUAGE TypeApplications #-}

Example

{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}

import qualified Data.ByteString as B
import Crypto.Hash.Algorithms (SHA512t_256)

inputs = ["a", "b", "c"] :: [B.ByteString]

-- create tree
t = merkleTree @SHA512t_256 inputs

-- create inclusion proof
p = either (error . show) id $ merkleProof 1 (inputs !! 1) t

-- verify proof
runMerkleProof p == merkleRoot t

TODO

  • implement extension of trees (possibly by linking memory chunks of maximal full trees) (how important is this?)
  • implement consistency proofs
  • document encodings and hash format
  • describe tree layout
Synopsis

Merkle Tree

data MerkleTree a Source #

Binary Merkle Tree.

A Merkle Tree is only an index. It doesn't store any data but only hashes of the data that is referenced in the tree.

Instances
Eq (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

(==) :: MerkleTree a -> MerkleTree a -> Bool #

(/=) :: MerkleTree a -> MerkleTree a -> Bool #

Show (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleTree a) :: Type -> Type #

Methods

from :: MerkleTree a -> Rep (MerkleTree a) x #

to :: Rep (MerkleTree a) x -> MerkleTree a #

NFData (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleTree a -> () #

ByteArrayAccess (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

length :: MerkleTree a -> Int #

withByteArray :: MerkleTree a -> (Ptr p -> IO a0) -> IO a0 #

copyByteArrayToPtr :: MerkleTree a -> Ptr p -> IO () #

type Rep (MerkleTree a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleTree a) = D1 (MetaData "MerkleTree" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "MerkleTree" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes)))

merkleTree :: forall a b. HasCallStack => HashAlgorithm a => ByteArrayAccess b => [MerkleNodeType a b] -> MerkleTree a Source #

Merkle Tree as described in RFC 6962, but with a configurable hash function and support for nested Merkle trees.

The Merkle tree for the empty input log is the hash of the empty string.

TODO: The length of the list is forced before the algorithm starts processing the items. Either demand a strict structure (e.g. vector or array) or allocate tree memory dynamically while traversing the log structure.

encodeMerkleTree :: ByteArray b => MerkleTree a -> b Source #

Binary encoding of a Merkle tree.

decodeMerkleTree :: forall a b m. MonadThrow m => HashAlgorithm a => ByteArrayAccess b => b -> m (MerkleTree a) Source #

Decode are Merkle tree from a binary representation.

Merkle Root

data MerkleRoot a Source #

The root of a Merkle tree.

Instances
Eq (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

(==) :: MerkleRoot a -> MerkleRoot a -> Bool #

(/=) :: MerkleRoot a -> MerkleRoot a -> Bool #

Ord (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Show (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleRoot a) :: Type -> Type #

Methods

from :: MerkleRoot a -> Rep (MerkleRoot a) x #

to :: Rep (MerkleRoot a) x -> MerkleRoot a #

NFData (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleRoot a -> () #

ByteArrayAccess (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

length :: MerkleRoot a -> Int #

withByteArray :: MerkleRoot a -> (Ptr p -> IO a0) -> IO a0 #

copyByteArrayToPtr :: MerkleRoot a -> Ptr p -> IO () #

type Rep (MerkleRoot a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleRoot a) = D1 (MetaData "MerkleRoot" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "MerkleRoot" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (MerkleHash a))))

merkleRoot :: forall a. HashAlgorithm a => MerkleTree a -> MerkleRoot a Source #

Get the root of Merkle tree.

encodeMerkleRoot :: ByteArray b => MerkleRoot a -> b Source #

Encode a Merkle tree root into binary format.

decodeMerkleRoot :: MonadThrow m => HashAlgorithm a => ByteArrayAccess b => b -> m (MerkleRoot a) Source #

Decode a Merkle tree root from a binary representation.

Merkle Proofs

data MerkleNodeType a b Source #

The Type of leafs nodes in a Merkle tree. A node is either an input value or a root of another nested Merkle tree.

Constructors

TreeNode (MerkleRoot a) 
InputNode b 
Instances
Functor (MerkleNodeType a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

fmap :: (a0 -> b) -> MerkleNodeType a a0 -> MerkleNodeType a b #

(<$) :: a0 -> MerkleNodeType a b -> MerkleNodeType a a0 #

Eq b => Eq (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

Ord b => Ord (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

Show b => Show (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleNodeType a b) :: Type -> Type #

Methods

from :: MerkleNodeType a b -> Rep (MerkleNodeType a b) x #

to :: Rep (MerkleNodeType a b) x -> MerkleNodeType a b #

NFData b => NFData (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleNodeType a b -> () #

type Rep (MerkleNodeType a b) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleNodeType a b) = D1 (MetaData "MerkleNodeType" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" False) (C1 (MetaCons "TreeNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (MerkleRoot a))) :+: C1 (MetaCons "InputNode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))

data MerkleProof a Source #

Merkle Inclusion Proof. In RFC 6962 this is called an audit proof. The proof in this module are not compatible with RFC 6962. They support proving inclusion of subtrees and proof for unbalanced trees of unknown size.

The proof is self-contained. It is independent of the concrete implementation of the Merkle tree. This type works with any binary Merkle tree type and doesn't make any assumptions about the balancing of the tree.

The proof includes the subject of the proof (for which inclusion is proven) as a plaintext bytestring. The proof does not include the root hash of the Merkle tree, because the proof is only meaningful if the root is available from a trusted source. Including it into the proof would thus be redundant or even misleading.

A more compact encoding would use the first bit of each hash to encode the side, but that would require to alter the hash computation. We also could pack the sides into a bit array. However, the total number of bytes for the sides will be most likely less than two hashes, so the overhead is small and doesn't justify more clever encodings.

Instances
Eq (MerkleProof a) Source # 
Instance details

Defined in Data.MerkleLog

Show (MerkleProof a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleProof a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleProof a) :: Type -> Type #

Methods

from :: MerkleProof a -> Rep (MerkleProof a) x #

to :: Rep (MerkleProof a) x -> MerkleProof a #

NFData (MerkleProof a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleProof a -> () #

type Rep (MerkleProof a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleProof a) = D1 (MetaData "MerkleProof" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" False) (C1 (MetaCons "MerkleProof" PrefixI True) (S1 (MetaSel (Just "_merkleProofSubject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MerkleProofSubject a)) :*: S1 (MetaSel (Just "_merkleProofObject") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (MerkleProofObject a))))

newtype MerkleProofSubject a Source #

The subject for which inclusion is proven.

Instances
Eq (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

Ord (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

Show (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleProofSubject a) :: Type -> Type #

NFData (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleProofSubject a -> () #

type Rep (MerkleProofSubject a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleProofSubject a) = D1 (MetaData "MerkleProofSubject" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "MerkleProofSubject" PrefixI True) (S1 (MetaSel (Just "_getMerkleProofSubject") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (MerkleNodeType a ByteString))))

data MerkleProofObject a Source #

Opaque proof object.

Instances
Eq (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

Show (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleProofObject a) :: Type -> Type #

NFData (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleProofObject a -> () #

ByteArrayAccess (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleProofObject a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleProofObject a) = D1 (MetaData "MerkleProofObject" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "MerkleProofObject" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes)))

encodeMerkleProofObject :: ByteArray b => MerkleProofObject a -> b Source #

Encode a Merkle proof object into binary format.

This copies the bytes of the underlying byte array. The encoded object doesn't reference the MerkleProofObject

decodeMerkleProofObject :: forall a b m. MonadThrow m => HashAlgorithm a => ByteArrayAccess b => b -> m (MerkleProofObject a) Source #

Encode a Merkle proof object from a binary representation.

This copies the original bytes and doesn't keep a reference to the input bytes.

merkleProof :: forall a m. MonadThrow m => HashAlgorithm a => MerkleNodeType a ByteString -> Int -> MerkleTree a -> m (MerkleProof a) Source #

Construct a self-contained Merkle inclusion proof.

merkleProof_ Source #

Arguments

:: MonadThrow m 
=> HashAlgorithm a 
=> MerkleNodeType a ByteString

The proof subject

-> NonEmpty (Int, MerkleTree a)

The proof components

-> m (MerkleProof a) 

Construct a Merkle proof for a proof subject in a nested sub-tree.

FIXME: make this function more efficient by implementing it more directly.

runMerkleProof :: forall a. HashAlgorithm a => MerkleProof a -> MerkleRoot a Source #

Execute an inclusion proof. The result of the execution is a Merkle root that must be compared to the trusted root of the Merkle tree.

Exceptions

newtype Expected a Source #

An expected value.

Constructors

Expected a 
Instances
Eq a => Eq (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

(==) :: Expected a -> Expected a -> Bool #

(/=) :: Expected a -> Expected a -> Bool #

Ord a => Ord (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

compare :: Expected a -> Expected a -> Ordering #

(<) :: Expected a -> Expected a -> Bool #

(<=) :: Expected a -> Expected a -> Bool #

(>) :: Expected a -> Expected a -> Bool #

(>=) :: Expected a -> Expected a -> Bool #

max :: Expected a -> Expected a -> Expected a #

min :: Expected a -> Expected a -> Expected a #

Show a => Show (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

showsPrec :: Int -> Expected a -> ShowS #

show :: Expected a -> String #

showList :: [Expected a] -> ShowS #

Generic (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (Expected a) :: Type -> Type #

Methods

from :: Expected a -> Rep (Expected a) x #

to :: Rep (Expected a) x -> Expected a #

NFData a => NFData (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: Expected a -> () #

type Rep (Expected a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (Expected a) = D1 (MetaData "Expected" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "Expected" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

newtype Actual a Source #

An actual value.

Constructors

Actual a 
Instances
Eq a => Eq (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

(==) :: Actual a -> Actual a -> Bool #

(/=) :: Actual a -> Actual a -> Bool #

Ord a => Ord (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

compare :: Actual a -> Actual a -> Ordering #

(<) :: Actual a -> Actual a -> Bool #

(<=) :: Actual a -> Actual a -> Bool #

(>) :: Actual a -> Actual a -> Bool #

(>=) :: Actual a -> Actual a -> Bool #

max :: Actual a -> Actual a -> Actual a #

min :: Actual a -> Actual a -> Actual a #

Show a => Show (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

showsPrec :: Int -> Actual a -> ShowS #

show :: Actual a -> String #

showList :: [Actual a] -> ShowS #

Generic (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (Actual a) :: Type -> Type #

Methods

from :: Actual a -> Rep (Actual a) x #

to :: Rep (Actual a) x -> Actual a #

NFData a => NFData (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: Actual a -> () #

type Rep (Actual a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (Actual a) = D1 (MetaData "Actual" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "Actual" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data MerkleTreeException Source #

Exceptions that are thrown by functions in Data.MerkleLog. All functions that throw exceptions can be called as pure functions in `Either SomeException`.

Instances
Eq MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

Show MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

Generic MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep MerkleTreeException :: Type -> Type #

Exception MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

NFData MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleTreeException -> () #

type Rep MerkleTreeException Source # 
Instance details

Defined in Data.MerkleLog

type Rep MerkleTreeException = D1 (MetaData "MerkleTreeException" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" False) ((C1 (MetaCons "EncodingSizeException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expected Int)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Actual Int)))) :+: (C1 (MetaCons "EncodingSizeConstraintException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expected Text)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Actual Int)))) :+: C1 (MetaCons "IndexOutOfBoundsException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Expected (Int, Int))) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Actual Int)))))) :+: (C1 (MetaCons "InputNotInTreeException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) :+: (C1 (MetaCons "MerkleRootNotInTreeException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) :+: C1 (MetaCons "InvalidProofObjectException" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

textMessage :: MerkleTreeException -> Text Source #

Display MerkleTreeException values as text messages.

Internal

isEmpty :: forall a. HashAlgorithm a => MerkleTree a -> Bool Source #

Test a Merkle tree is the tree of the empty log.

emptyMerkleTree :: forall a. HashAlgorithm a => MerkleTree a Source #

The Merkle tree of the empty log. RFC 6962 specifies that this is the hash of the empty string.

size :: forall a. HashAlgorithm a => MerkleTree a -> Int Source #

The number of nodes (including leafs) in a Merkle tree.

leafCount :: HashAlgorithm a => MerkleTree a -> Int Source #

Get the number of leafs in a Merkle tree.

data MerkleHash a Source #

Internal type to represent hash values.

Instances
Eq (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

(==) :: MerkleHash a -> MerkleHash a -> Bool #

(/=) :: MerkleHash a -> MerkleHash a -> Bool #

Ord (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Show (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Generic (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Associated Types

type Rep (MerkleHash a) :: Type -> Type #

Methods

from :: MerkleHash a -> Rep (MerkleHash a) x #

to :: Rep (MerkleHash a) x -> MerkleHash a #

NFData (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

rnf :: MerkleHash a -> () #

ByteArrayAccess (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

Methods

length :: MerkleHash a -> Int #

withByteArray :: MerkleHash a -> (Ptr p -> IO a0) -> IO a0 #

copyByteArrayToPtr :: MerkleHash a -> Ptr p -> IO () #

type Rep (MerkleHash a) Source # 
Instance details

Defined in Data.MerkleLog

type Rep (MerkleHash a) = D1 (MetaData "MerkleHash" "Data.MerkleLog" "merkle-log-0.1.0.0-4JJg1LvWubF6HYXmsOGsa9" True) (C1 (MetaCons "MerkleHash" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bytes)))

getHash :: HashAlgorithm a => MerkleTree a -> Int -> MerkleHash a Source #

Get the hash of a node in the Merkle tree.

merkleLeaf :: forall a b. HashAlgorithm a => ByteArrayAccess b => b -> MerkleHash a Source #

Compute hash for a leaf node in a Merkle tree.

merkleNode :: forall a. HashAlgorithm a => MerkleHash a -> MerkleHash a -> MerkleRoot a Source #

Compute hash for an inner node of a Merkle tree.