Safe Haskell | None |
---|---|
Language | Haskell2010 |
Two-way (binary) Merkle Hash Trees which implements append-only logs and provides both inclusion proof and consistency proof. The API design is inspired by Certificate Transparency defined in RFC 6962.
- data Settings inp ha
- defaultSettings :: Settings ByteString SHA256
- hash0 :: Settings inp ha -> Digest ha
- hash1 :: Settings inp ha -> inp -> Digest ha
- hash2 :: Settings inp ha -> Digest ha -> Digest ha -> Digest ha
- data MerkleHashTrees inp ha
- info :: MerkleHashTrees inp ha -> (TreeSize, Digest ha)
- size :: MerkleHashTrees inp ha -> TreeSize
- digest :: TreeSize -> MerkleHashTrees inp ha -> Maybe (Digest ha)
- type TreeSize = Int
- type Index = Int
- empty :: Settings inp ha -> MerkleHashTrees inp ha
- fromList :: (ByteArrayAccess inp, HashAlgorithm ha) => Settings inp ha -> [inp] -> MerkleHashTrees inp ha
- add :: (ByteArrayAccess inp, HashAlgorithm ha) => inp -> MerkleHashTrees inp ha -> MerkleHashTrees inp ha
- data InclusionProof ha
- defaultInclusionProof :: InclusionProof ha
- leafIndex :: InclusionProof ha -> Index
- treeSize :: InclusionProof ha -> TreeSize
- inclusion :: InclusionProof ha -> [Digest ha]
- generateInclusionProof :: Digest ha -> TreeSize -> MerkleHashTrees inp ha -> Maybe (InclusionProof ha)
- verifyInclusionProof :: (ByteArrayAccess inp, HashAlgorithm ha) => Settings inp ha -> Digest ha -> Digest ha -> InclusionProof ha -> Bool
- data ConsistencyProof ha
- defaultConsistencyProof :: ConsistencyProof ha
- firstTreeSize :: ConsistencyProof ha -> TreeSize
- secondTreeSize :: ConsistencyProof ha -> TreeSize
- consistency :: ConsistencyProof ha -> [Digest ha]
- generateConsistencyProof :: TreeSize -> TreeSize -> MerkleHashTrees inp ha -> Maybe (ConsistencyProof ha)
- verifyConsistencyProof :: (ByteArrayAccess inp, HashAlgorithm ha) => Settings inp ha -> Digest ha -> Digest ha -> ConsistencyProof ha -> Bool
Settings
Settings for Merkle Hash Trees. The first parameter is input data type. The second one is digest data type.
To create this, use defaultSettings
:
defaultSettings { hash0 = ..., hash1 = ..., hash2 = ... }
defaultSettings :: Settings ByteString SHA256 Source #
A default Settings with ByteString
and SHA256
.
This can be used for CT(Certificate Transparency) defined in RFC 6962.
Accessors
hash1 :: Settings inp ha -> inp -> Digest ha Source #
A hash function for one input element to calculate the leaf digest.
hash2 :: Settings inp ha -> Digest ha -> Digest ha -> Digest ha Source #
A hash function for two input elements to calculate the internal digest.
Merkle Hash Trees
data MerkleHashTrees inp ha Source #
The data type for Merkle Hash Trees. The first parameter is input data type. The second one is digest data type.
Accessors
info :: MerkleHashTrees inp ha -> (TreeSize, Digest ha) Source #
Getting the root information of the Merkle Hash Tree. A pair of the current size and the current Merle Tree Hash is returned.
size :: MerkleHashTrees inp ha -> TreeSize Source #
Getting the log size
digest :: TreeSize -> MerkleHashTrees inp ha -> Maybe (Digest ha) Source #
Getting the Merkle Tree Hash.
Related types
Creating Merkle Hash Trees
empty :: Settings inp ha -> MerkleHashTrees inp ha Source #
Creating an empty MerkleHashTrees
.
>>>
info $ empty defaultSettings
(0,e3b0c44298fc1c149afbf4c8996fb92427ae41e4649b934ca495991b7852b855)
fromList :: (ByteArrayAccess inp, HashAlgorithm ha) => Settings inp ha -> [inp] -> MerkleHashTrees inp ha Source #
Creating a Merkle Hash Tree from a list of elements. O(n log n)
>>>
info $ fromList defaultSettings ["0","1","2"]
(3,725d5230db68f557470dc35f1d8865813acd7ebb07ad152774141decbae71327)
Appending an element
add :: (ByteArrayAccess inp, HashAlgorithm ha) => inp -> MerkleHashTrees inp ha -> MerkleHashTrees inp ha Source #
Adding (appending) an element. O(log n)
>>>
info $ add "1" $ empty defaultSettings
(1,2215e8ac4e2b871c2a48189e79738c956c081e23ac2f2415bf77da199dfd920c)
Inclusion Proof
data InclusionProof ha Source #
The type for inclusion proof (aka audit proof).
Eq (InclusionProof ha) Source # | |
Show (InclusionProof ha) Source # | |
defaultInclusionProof :: InclusionProof ha Source #
The default value for InclusionProof
just to create a new value.
Accessors
leafIndex :: InclusionProof ha -> Index Source #
The index for the target.
treeSize :: InclusionProof ha -> TreeSize Source #
The hash tree size.
inclusion :: InclusionProof ha -> [Digest ha] Source #
A list of digest for inclusion.
Proof and verification
generateInclusionProof Source #
:: Digest ha | The target hash (leaf digest) |
-> TreeSize | The tree size |
-> MerkleHashTrees inp ha | |
-> Maybe (InclusionProof ha) |
Generating InclusionProof
for the target at the server side.
:: (ByteArrayAccess inp, HashAlgorithm ha) | |
=> Settings inp ha | |
-> Digest ha | The target hash (leaf digest) |
-> Digest ha | Merkle Tree Hash (root digest) for the tree size |
-> InclusionProof ha | InclusionProof of the target |
-> Bool |
Verifying InclusionProof
at the client side.
>>>
let target = "3"
>>>
let mht = fromList defaultSettings ["0","1","2",target,"4","5","6"]
>>>
let treeSize = 5
>>>
let leafDigest = hash1 defaultSettings target
>>>
let Just proof = generateInclusionProof leafDigest treeSize mht
>>>
let Just rootDigest = digest treeSize mht
>>>
verifyInclusionProof defaultSettings leafDigest rootDigest proof
True
Consistency Proof
data ConsistencyProof ha Source #
The type for consistency proof.
Eq (ConsistencyProof ha) Source # | |
Show (ConsistencyProof ha) Source # | |
defaultConsistencyProof :: ConsistencyProof ha Source #
The default value for ConsistencyProof
just to create a new value.
Accessors
firstTreeSize :: ConsistencyProof ha -> TreeSize Source #
The first hash tree size.
secondTreeSize :: ConsistencyProof ha -> TreeSize Source #
The second hash tree size.
consistency :: ConsistencyProof ha -> [Digest ha] Source #
A list of digest for consistency.
Proof and verification
generateConsistencyProof :: TreeSize -> TreeSize -> MerkleHashTrees inp ha -> Maybe (ConsistencyProof ha) Source #
Generating ConsistencyProof
for the target at the server side.
verifyConsistencyProof :: (ByteArrayAccess inp, HashAlgorithm ha) => Settings inp ha -> Digest ha -> Digest ha -> ConsistencyProof ha -> Bool Source #
Verifying ConsistencyProof
at the client side.
>>>
let mht0 = fromList defaultSettings ["0","1","2","3"]
>>>
let (m, digestM) = info mht0
>>>
let mht1 = add "6" $ add "5" $ add "4" mht0
>>>
let (n, digestN) = info mht1
>>>
let Just proof = generateConsistencyProof m n mht1
>>>
verifyConsistencyProof defaultSettings digestM digestN proof
True