merkle-tree-0.1.1: An implementation of a Merkle tree and merkle tree proofs of inclusion

Safe HaskellNone
LanguageHaskell2010

Crypto.Hash.MerkleTree

Contents

Synopsis

Documentation

data MerkleTree a Source #

A merkle tree.

Instances
Foldable MerkleTree Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

fold :: Monoid m => MerkleTree m -> m #

foldMap :: Monoid m => (a -> m) -> MerkleTree a -> m #

foldr :: (a -> b -> b) -> b -> MerkleTree a -> b #

foldr' :: (a -> b -> b) -> b -> MerkleTree a -> b #

foldl :: (b -> a -> b) -> b -> MerkleTree a -> b #

foldl' :: (b -> a -> b) -> b -> MerkleTree a -> b #

foldr1 :: (a -> a -> a) -> MerkleTree a -> a #

foldl1 :: (a -> a -> a) -> MerkleTree a -> a #

toList :: MerkleTree a -> [a] #

null :: MerkleTree a -> Bool #

length :: MerkleTree a -> Int #

elem :: Eq a => a -> MerkleTree a -> Bool #

maximum :: Ord a => MerkleTree a -> a #

minimum :: Ord a => MerkleTree a -> a #

sum :: Num a => MerkleTree a -> a #

product :: Num a => MerkleTree a -> a #

Eq a => Eq (MerkleTree a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

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

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

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

Defined in Crypto.Hash.MerkleTree

Generic (MerkleTree a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Associated Types

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

Methods

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

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

Serialize a => Serialize (MerkleTree a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

put :: Putter (MerkleTree a) #

get :: Get (MerkleTree a) #

type Rep (MerkleTree a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

type Rep (MerkleTree a) = D1 (MetaData "MerkleTree" "Crypto.Hash.MerkleTree" "merkle-tree-0.1.1-KAmiIlQ92ETGO74OSAt4KB" False) (C1 (MetaCons "MerkleEmpty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MerkleTree" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word32) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (MerkleNode a))))

newtype MerkleRoot a Source #

A merkle tree root.

Constructors

MerkleRoot 
Instances
Eq (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

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

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

Ord (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Show (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Generic (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Associated Types

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

Methods

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

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

Serialize (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

put :: Putter (MerkleRoot a) #

get :: Get (MerkleRoot a) #

ByteArrayAccess (MerkleRoot a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

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 Crypto.Hash.MerkleTree

type Rep (MerkleRoot a) = D1 (MetaData "MerkleRoot" "Crypto.Hash.MerkleTree" "merkle-tree-0.1.1-KAmiIlQ92ETGO74OSAt4KB" True) (C1 (MetaCons "MerkleRoot" PrefixI True) (S1 (MetaSel (Just "getMerkleRoot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

data MerkleNode a Source #

Constructors

MerkleBranch 
MerkleLeaf 

Fields

Instances
Foldable MerkleNode Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

fold :: Monoid m => MerkleNode m -> m #

foldMap :: Monoid m => (a -> m) -> MerkleNode a -> m #

foldr :: (a -> b -> b) -> b -> MerkleNode a -> b #

foldr' :: (a -> b -> b) -> b -> MerkleNode a -> b #

foldl :: (b -> a -> b) -> b -> MerkleNode a -> b #

foldl' :: (b -> a -> b) -> b -> MerkleNode a -> b #

foldr1 :: (a -> a -> a) -> MerkleNode a -> a #

foldl1 :: (a -> a -> a) -> MerkleNode a -> a #

toList :: MerkleNode a -> [a] #

null :: MerkleNode a -> Bool #

length :: MerkleNode a -> Int #

elem :: Eq a => a -> MerkleNode a -> Bool #

maximum :: Ord a => MerkleNode a -> a #

minimum :: Ord a => MerkleNode a -> a #

sum :: Num a => MerkleNode a -> a #

product :: Num a => MerkleNode a -> a #

Eq a => Eq (MerkleNode a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

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

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

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

Defined in Crypto.Hash.MerkleTree

Generic (MerkleNode a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Associated Types

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

Methods

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

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

Serialize a => Serialize (MerkleNode a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

put :: Putter (MerkleNode a) #

get :: Get (MerkleNode a) #

type Rep (MerkleNode a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Constructors

Merkle Proof

newtype MerkleProof a Source #

Constructors

MerkleProof 

Fields

Instances
Eq (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Ord (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Show (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Generic (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Associated Types

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

Methods

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

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

Serialize (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

Methods

put :: Putter (MerkleProof a) #

get :: Get (MerkleProof a) #

type Rep (MerkleProof a) Source # 
Instance details

Defined in Crypto.Hash.MerkleTree

type Rep (MerkleProof a)

merkleProof :: forall a. MerkleTree a -> MerkleRoot a -> MerkleProof a Source #

Construct a merkle tree proof of inclusion Walks the entire tree recursively, building a list of "proof elements" that are comprised of the current node's root and it's sibling's root, and whether it is the left or right sibling (this is necessary to determine the order in which to hash each proof element root and it's sibling root). The list is ordered such that the for each element, the next element in the list is the proof element corresponding to the node's parent node.

validateMerkleProof :: forall a. MerkleProof a -> MerkleRoot a -> MerkleRoot a -> Bool Source #

Validate a merkle tree proof of inclusion

Size

mtRoot :: MerkleTree a -> MerkleRoot a Source #

Returns root of merkle tree.

mtHash :: MerkleTree a -> ByteString Source #

Returns root of merkle tree root hashed.

mtHeight :: Int -> Int Source #

Merkle tree height

Testing

testMerkleProofN :: Int -> IO Bool Source #

Constructs a merkle tree and random leaf root to test inclusion of