Compute the Merkle Tree of Bitcoin blocks using Haskell's cryptonite
EDIT 4/11/2019: If you want to follow along, the full code described in this post has been uploaded to GitHub here, though beware some things are little bit different as some additions and amendments have been made.
In this post we will learn about how to compute the Merkle Tree Root hash for any bitcoin block, how to build a proof so that other nodes can check a specific transaction is within the block and finally how to verify such proof just by using a subset of the transactions in the block and the Merkle Tree Root hash, all of these in Haskell, isn’t that exiting 😍, let’s begin!.
In bitcoin a Merkle Tree Root hash is used as a verification mechanism so that a node can check that transactions included in the block are legitimate. It also can be used by nodes in the network to quickly verify that a transaction is included in a block without the need to store the whole block!. As an introduction I recommend watching this video:
Computing the Merkle Tree Root hash
Ok, now we have the intuition about how the Merkle Tree Root hash is computed, first all transactions in the block are hashed and these are organized in a binary tree structure where parent nodes are the hash of the child nodes concatenated, these continues up to the tree root which is called the Merkle Tree Root hash. Here is a quick diagram to clarify the concept:
In order to build the algorithm that will do this we consult the Bitcoin Wiki on Merkle Trees here I quote:
Merkle trees are binary trees of hashes. Merkle trees in bitcoin use a double SHA-256, the SHA-256 hash of the SHA-256 hash of something.
If, when forming a row in the tree (other than the root of the tree), it would have an odd number of elements, the final double-hash is duplicated to ensure that the row has an even number of hashes.
First form the bottom row of the tree with the ordered double-SHA-256 hashes of the byte streams of the transactions in the block.
Then the row above it consists of half that number of hashes. Each entry is the double-SHA-256 of the 64-byte concatenation of the corresponding two hashes below it in the tree.
This procedure repeats recursively until we reach a row consisting of just a single double-hash. This is the Merkle root of the tree.
In Haskell we can use functions from the Crypto.Hash
module in the the
Cryptonite package to compute hashes. For example, hashing a simple string
with SHA-256 can be done using the hashWith
function like this:
λ > import Crypto.Hash (hashWith, SHA256(..))
λ > import Data.ByteString (ByteString)
λ > hashWith SHA256 ("hello" :: ByteString)
2cf24dba5fb0a30e26e83b2ac5b9e29e1b161e5c1fa7425e73043362938b9824
Note: you need OverloadedStrings
extension enabled for this.
So when we hash hello
using the SHA-256 algorithm we get the following
digest:
2cf24dba5fb0a30e26e83b2ac5b9e29e1b161e5c1fa7425e73043362938b9824
The result of the hashWith
function has the type Digest SHA256
, this is a
phantom type, because we really don’t have a value of type SHA256
, it is
used in the type system so we can’t treat digests of different algorithms as
the same. For clarity, here is the definition of the Digest
type.
Now, in a Merkle Tree what we’ll hash are blockchain transactions, in this
post we will be working with block
0000000000000168fe7db3e00e748a335d39c33752c5095a85ccdab7d0184845
from the
bitcoin network, this block was mined back in May 2013 so it was way before
the Bitcoin Cash fork happened, so you can see it in any block explorer. This
block has only four transactions, this is great since explaining the
algorithm will be so much easier, however our code will work for any number
of transactions.
These are the transactions hashes from this block:
1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05
80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2
5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02
The algorithm
According to the Bitcoin wiki in order to compute the Merkle Tree Root hash one should:
- Take a list of all the transactions in the block.
- Group the transactions in pairs.
- For each pair:
- Concatenate the elements.
- Double hash the result.
- Save result in a list of hashes.
- Repeat all steps until a single hash remains.
Although we can build the binary tree and compute the MTR hash from it, here we will compute it from a list of transactions for simplicity, but towards the end of the post we’ll see how the tree is built. We will need a function to group elements from a list in pairs, I don’t know if such function already exists in the Prelude (I couldn’t find any) so we define our own function like this:
-- | Groups by two the adjancent elements in a list starting from the left.
-- If the list length is odd the last element is grouped with itself.
byTwo :: [a] -> [(a, a)]
byTwo [] = []
byTwo [x] = [(x, x)]
byTwo (x : y : zs) = (x, y) : byTwo zs
This function takes a list and gives back a list of pairs, in the case the
given list is empty we just give back an empty list, if the list has only a
single element then we pair that element with itself; this is because
according to the wiki the last transaction in a odd-length list will be
hashed with itself. Finally, we take the first and second elements from the
list, create a pair and cons that with the result of recursively apply the
byTwo
function to the rest of the list (the zs
in this case). With this
we can do what step 1 and 2 are about.
Now, for the third step we need concatenate the elements and hash the
result, we can make a single function called combine
that given two
digests performs this as a black box. In the bitcoin wiki one could see the
following note:
Note: Hashes in Merkle Tree displayed in the Block Explorer are of little-endian notation. For some implementations and calculations, the bytes need to be reversed before they are hashed, and again after the hashing operation.
So after concatenating the transactions we need to first reverse the result, hash it using the SHA-256 algorithm twice and then reverse it back again. So if we have these two transactions:
ee6bc0e5f95a4ccd0f00784eab850ff8593f9045de96c6656df41c8f9f9c0888
29c59ec39fc19afd84d928272b3290bbe54558f7b51f75feb858b005dea49c10
We perform this steps:
-
Concatenate
ee6bc0...
to the end of29c59e...
to get:29c59ec39fc19afd84d928272b3290bbe54558f7b51f75feb858b005dea49c10ee6bc0e5f95a4ccd0f00784eab850ff8593f9045de96c6656df41c8f9f9c0888
-
Reverse the result to get:
8880c9f9f8c14fd6566c69ed5409f3958ff058bae48700f0dcc4a59f5e0cb6ee01c94aed500b858bef57f15b7f85545ebb0923b272829d48dfa91cf93ce95c92
-
Compute the double SHA-256 hash of it to get:
10ef4fc57210805877fddf7329b702ad21a9cc6e03f3b23a11c60e234b8f5a10
-
Reverse the result:
01a5f8b432e06c11a32b3f30e6cc9a12da207b9237fddf77850801275cf4fe01
And guess what? we just have computed the Merkle Tree Root hash for block #371623!, this is because that block only has two transactions so the algorithm doesn’t need to be repeated.
Let’s define a function to do all of this:
-- | Given two digest it combines them as Bitcoin does it.
combine :: forall a. HashAlgorithm a => Digest a -> Digest a -> Digest a
combine h g = merge h g
& ByteString.reverse
& doubleHash
& ByteArray.convert
& ByteString.reverse
& digestFromByteString
& fromJust
where
merge x y = ByteArray.concat [y, x] :: ByteString
doubleHash a = hash (hash a :: Digest a) :: Digest a
We could write a more specific version of this function that will only work
with values of type Digest SHA256
but I didn’t, this combine function
works for any type of Digest a
where a
is an instance of
HashAlgorithm
, that is any hashing algorithm in the
Crypto.Hash.Algorithms
module. I know it’s better to use function
composition but for this function involving several steps I find it clearer
to use the pipe operator & (shouldn’t this operator be |>
like in F#,
Elixir or Elm?).
Let’s explain. First we use the merge
function defined in local scope,
this function has a bad name to not clash with the concat
function from
the prelude, what it does is to concat the given digests, we use the
concat
function from the Data.ByteArray
module, we do this because
every digest (as a ByteString
) is also an instance of the
ByteArrayAccess
type class, we type cast the result to clarify that the
ByteArray
we get back should be a ByteString
. After concatenating with
the merge
function we pass the result to the reverse
function from the
Data.ByteString
module and double hash the result with the locally defined
doubleHash
function.
doubleHash a = hash (hash a :: Digest a) :: Digest a
This function takes a value a
, it’s just a ByteString
, we hash it using
the hash
function from the Crypto.Hash
module, note we can’t use
hashWith
function here because then we would have to know what the a
at
the type level is, so the hash
function will do, we just type cast the
result to be a Digest a
then hash the result again to get a second Digest a
, here we see why we use existential quantification, by adding forall a.
at the type signature for the combine
function, this way the compiler will
know the a
we’re referring to here, should be the same a
of the
generated digest, basically we’re tying the hashing algorithm used when
calling combine
with the algorithm used in the doubleHash
inner
function. Just remember that for this to work we need to enable the
ScopedTypeVariables
extension, otherwise forall
will not be recognized
as a valid keyword.
Ok, after that we reverse back again and use digestFromByteString
from
the Cryptonite package to take a ByteString
and literally just package it
in a Digest a
, of course this only works if the ByteString
has the
correct byte size, this function gives us a Maybe (Digest a)
value back,
so we use the fromJust
function from the Data.Maybe
module to extract
the value, as far as I can tell we can not get a Nothing
value back, the
type signature enforces this function will work for any a
, given that a
is a HashAlgorithm
and this algorithm is the same used in all steps of the
combine
function, so the digestFromByteString
function will always work
as the bytestring will have the correct byte size every time.
With this, we have enough to implement the full algorithm:
-- | Computes the Merkle Tree Root of the given list of 'Tx'.
merkleRoot :: [ Tx ] -> Digest SHA256
merkleRoot txs
| length reduced == 1 = head reduced
| otherwise = merkleRoot reduced
where
reduced = map (uncurry combine) $ byTwo txs
Note that Tx
is just a type alias to Digest SHA256
:
type Tx = Digest SHA256
Nothing fancy there. The merkleRoot
function takes a list of transactions
and if this list has length one we just return the head element, otherwise
we recursively call merkleRoot
on the reduced list. The reduced
list
is computed by grouping by two the elements of the list and then map every
pair through the combine
function, we use uncurry
so that the combine
function can work on pairs. Note that we could’ve defined this function
using pattern matching instead of guards, but if done that way the compiler
will warn about not matching the empty list []
, if given an empty list we
can’t give a Digest SHA256
value back, so this function is not total, for
this we could use the Maybe
Functor, thus having a computation with type
[ Tx ] -> Maybe (Digest SHA256)
, you know what this means? 😏, that’s
right, Monadic code 😎:
merkleRoot :: [ Tx ] -> Maybe (Digest SHA256)
merkleRoot [] = Nothing
merkleRoot [x] = Just x
merkleRoot txs = do
let reduced = map (uncurry combine) $ byTwo txs
merkleRoot reduced
Note that by using a Monad we could work with any Monad, not just the
Maybe
Monad, also we can avoid do
notation all together if we pack all
into one expression, I’ll let that as an exercise for the reader, the
important thing is that we now have a total function that computes the
Merkle Tree Root hash. Now on to the next task.
Building a Merkle Tree Proof
We now have the function that makes it possible to compute the Merkle Root hash given a list of transactions, now suppose we’re certain a transaction is on a given block and we want other node to confirm that, for this we need to build a Merkle Tree Proof. A proof consists of providing the siblings of the hashes that get combined with our transaction’s hash all the way up to the
In the figure 2 above we can see that in order to construct a
proof proving that K
is in the block, we only need to provide it’s hash,
L
’s hash, IJ
’s hash, MNOP
’s hash and ABCDEFGH
’s hash. If every hash
consists of 32 bytes (SHA-256 has 256 bit length), instead of providing all
of the 15
other transactions for a total of 15 * 32 = 480
bytes we just
need 4 * 32 = 128
bytes, that’s a 73.33% discount in space! This is because
an optimal algorithm takes O(log n) in order to find an item down the tree.
The algorithm
The algorithm we will use to compute the proof is the following:
- Take a list of all transactions in the block and a single transaction for which to build the proof of inclusion in such a block.
- Group the transactions in pairs.
- Find the pair that contains the given transaction for which we want to construct the proof.
- If the transaction is the first component of the pair return the second
component as a
Right
. Otherwise, return the first component wrapped in aLeft
. This effectively gets the sibling of the transaction. - Save sibling in the proof list.
- Combine the pair in which the transaction was found and save the resulting hash.
- Combine all the pairs generated in step 2.
- Repeat all steps, this time the transaction list is the list of hashes generated in step 7 whereas the transaction to look for is a hash digest generated in step 6. Do this until the list of transactions is a singleton list.
This algorithm is a little more complex, please do tell @ZzAntares for a
simpler one 🙏. By using the block #234132 we will build a proof of
inclusion for the 94d67a...
transaction. This is the list of transactions:
[ 1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
, 94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05
, 80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2
, 5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02
]
First, group transactions by pairs:
[ ( 1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
, 94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05
)
, ( 80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2
, 5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02
)
]
Now, the 94d67a...
transaction is the second component of the first pair,
so we should save the sibling transaction 1877fc...
in a Left
because
it’s the first component of the first tuple:
Proof element =>
Left 1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
We should save this proof element in to the proof list:
Proof list =>
[ Left 1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
]
Now lets combine the pair in which the transaction was found, these are
combined using the combine
function we defined above to get this result:
Combined pair =>
0abb8731e8103dee8ab2223d37cbc9f86399d9175c1efa709fa3edb6f6e61d84
We save this result as the next transaction. Then we also combine all other pairs, thus getting a list of hashes:
Combined pairs =>
0abb8731e8103dee8ab2223d37cbc9f86399d9175c1efa709fa3edb6f6e61d84
913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435
Now, we repeat the same steps, using the combined pair as the next “transaction” to look for and the combined pairs as the list of “transactions” in the block.
Let’s group the hashes in pairs again:
[ ( 0abb8731e8103dee8ab2223d37cbc9f86399d9175c1efa709fa3edb6f6e61d84
, 913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435
)
]
And find the pair in which the “transaction” we’re looking for is, there’s
only one pair and 0abb87...
is the first component of the pair, so we
should wrap the second component in a Right
:
Proof element =>
Right 913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435
And we should add this proof element to the proof list:
Proof list =>
[ Left 1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
, Right 913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435
]
If we go on recursively through our algorithm we must combine the only pair we have and pass the list of transactions (that now it will be a singleton list) to the function, this time we stop as we don’t have any more pairs.
Now let’s see how to build the Merkle Tree Proof using these algorithm in Haskell:
merkleProof :: [ Tx ] -> Tx -> [ Either (Digest SHA256) (Digest SHA256) ]
merkleProof [] _ = [] -- To avoid compiler warning
merkleProof [_] _ = []
merkleProof txs tx =
let
siblingOf :: Digest SHA256 -> [ (Digest SHA256, Digest SHA256) ] -> Either (Digest SHA256) (Digest SHA256)
siblingOf x = toEither . fromJust . find (elem x)
where
toEither (a, b)
| a == x = Right b
| otherwise = Left a
merge :: Either (Digest SHA256) (Digest SHA256) -> Digest SHA256 -> Digest SHA256
merge (Left h) g = combine h g
merge (Right h) g = combine g h
byTwoTxs = byTwo txs
sibling = siblingOf tx byTwoTxs
in
sibling : merkleProof (uncurry combine <$> byTwoTxs) (merge sibling tx)
Note that the code would be somewhat nicer if we used a custom data type
instead of Either
, this is because Either
is parameterized by two types,
our custom data type will only need one since we know both left and right
values will have the same type.
Ok let’s explain this monstrous function piece by piece, we start by
defining a local helper function called siblingOf
, this one takes a hash
digest and a list of pairs of hashes, and returns either a Left
or a
Right
with a hash digest tucked in. What it does is to use find
on the
list of pairs to find the tuple containing the given hash as first
argument. We use the inner function toEither
to correctly wrap the sibling
of the given transaction, Left
is given if the sibling is the first
component, Right
otherwise. For the trained eye, elem
doesn’t work on
tuples, here we refer to a custom elem
function defined here.
Next, we create another local helper function, this one just takes either a
Left
or a Right
value and hashes it with the digest given as second
argument, the catch is that if the first argument is a Right
then when
combining the hashes the second argument goes as the first argument to the
combine function, otherwise is the opposite.
Now, to construct the proof we retrieve the sibling of the given transaction
by using the siblingOf
function on the transaction list after its elements
have been grouped in pairs (this results in an Either
), and cons that
with the result of recursively apply the function to the list that results
in combining the pairs in the grouped list of transactions. And the
transaction to look for will be the result of combining the hashes through
the merge
function. Our base case will return an empty list and the proof
will be constructed starting from that empty list.
Note that our merkleProof
function doesn’t account for a missing hash,
right now if we give to it a transaction that we now for sure is not in the
block it will fail miserably, why don’t you try using Maybe
to account for
that? I’ll provide a link to my solutions at the end so you can compare.
Merkle Tree Proof as means to Simplified Payment Verification
As mentioned earlier in the post, the proof of inclusion for a transaction in a block can be used by any other node in the network without the need to have downloaded the entirety of the block. In bitcoin this allows for a simplified mechanism to verify that a transaction “went through”, as per the bitcoin wiki on simplified payment verification:
… it is possible to verify bitcoin payments without running a full network node. And this is called simplified payment verification or SPV. A user or user’s bitcoin spv wallet only needs a copy of the block headers of the longest chain, which are available by querying network nodes until it is apparent that the longest chain has been obtained. Then, wallet using spv client get the Merkle branch linking the transaction to its block. Linking the transaction to a place in the active chain demonstrates that a network node has accepted it, and blocks added after it further establish the confirmation.
In this way, correct execution of the process of constructing the proof is in itself the proof that a transaction is within the block, if this wasn’t the case, at some point we would have failed to find a hash in the list of hash pairs. This trickery is what makes the simplified payment verification on bitcoin work:
Now, if we’re given a proof how do we know is correct? You can imagine I give to you a transaction and a proof of inclusion of such transaction in a particular block, you don’t have to trust me if you already have the Merkle Tree Root hash of such block, then we just need to start hashing each element in the proof starting with the transaction we’re checking and if we end with the same hash as the Merkle Tree Root hash then we know the proof is correct and the transaction is indeed in the block. Here is a function that does just this:
verify :: Tx -> Digest SHA256 -> [ Either (Digest SHA256) (Digest SHA256) ] -> Bool
verify tx mkr proof = (== mkr) $ foldl prover tx proof
where
prover :: Digest SHA256 -> Either (Digest SHA256) (Digest SHA256) -> Digest SHA256
prover h (Left x) = combine x h
prover h (Right x) = combine h x
Given a transaction, a merkle root hash and a proof, we fold the proof hashing at each step the resulting hash with the next element in the proof, at the end the final hash should be the same as the Merkle Tree Root hash.
Testing
It’s time to go back to our transaction list on block #234132:
1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b
94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05
80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2
5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02
As these transactions id’s are just Text
, we’ll build a function that turns
them into hash digests, a function of type Text -> Digest SHA256
, in the
following code Tx
is a type alias to Digest SHA256
:
-- | Given a 'Text' of a Hex representation SHA256 digest turns it into a Tx.
parseSHA256 :: Text -> Maybe Tx
parseSHA256 t
| isHex t = parse t
| otherwise = Nothing
where
parse = digestFromByteString . Hex.toBytes . Hex.hexString . Text.encodeUtf8
isHex = Text.all Char.isHexDigit
We check all the characters in the Text
are hexadecimal, we could also
check the length to be 64
characters but the digestFromByteString
function already takes care of return Nothing
when the size does not match
the one used in the specified hashing algorithm.
Now we can take our Text
transactions, load’em up and compute our Merkle
stuff on them. To ease and automate the testing of our functions I’m going to
write a HUnit spec, first, we test our parsing function that turns Text
transactions into Digest SHA256
actual hashes:
describe "### Crypto.Merkle.parseSHA256" $ do
it "turns Text of a SHA256 hex representation into an actual Digest" $ do
let sha256 = "2cf24dba5fb0a30e26e83b2ac5b9e29e1b161e5c1fa7425e73043362938b9824"
expected = Just $ hashWith SHA256 ("hello" :: ByteString)
parseSHA256 sha256 `shouldBe` expected
parseSHA256 "abcd" `shouldBe` Nothing
parseSHA256 "nada" `shouldBe` Nothing
All the functions written in this post are living in a module called
Crypto.Merkle
more details on this latter, aside from that there’s nothing
new under the sun here, now, we test the combine
function, it should
combine two hashes the way its needed for computing the merkle tree in
bitcoin:
describe "### Crypto.Merkle.combine" $
it "combines two Digest SHA256 into one using little-endian format" $ do
let [tx1, tx2, mkr] = fromJust . parseSHA256 <$>
[ "ee6bc0e5f95a4ccd0f00784eab850ff8593f9045de96c6656df41c8f9f9c0888"
, "29c59ec39fc19afd84d928272b3290bbe54558f7b51f75feb858b005dea49c10"
, "01a5f8b432e06c11a32b3f30e6cc9a12da207b9237fddf77850801275cf4fe01"
]
combine tx1 tx2 `shouldBe` mkr
Here we use the Functor instance on lists to map a composite function that
parses each of the Text
transactions into Digest SHA256
and extract the
value tucked in the Maybe
, it is safe to use fromJust
since the given
Text
hashes are valid SHA256 hashes.
Ok, now to compute the Merkle Tree Root hash with the function merkleRoot
:
describe "### Crypto.Merkle.merkleRoot" $ do
it "computes merkle tree root from an even list of SHA256 hex text" $ do
let mkr = "74fe176dcfe07bf6e0ef0f9ee63c81b78623ac9b03137d5f4cfd80f0e500a7c3"
txs =
[ "1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b"
, "94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05"
, "80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2"
, "5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02"
]
rtx = fromJust $ traverse parseSHA256 txs
expected = parseSHA256 mkr
merkleRoot rtx `shouldBe` expected
Now in this one we use the clever traverse
function, we can think of it
like a map with a twist at the end, instead of giving us a list of maybe
values it gives us a maybe of a list ([ Maybe (Digest SHA256) ] -> Maybe [ Digest SHA256 ]
) then we extract the list using fromJust
, again, is safe
to do it because all Text
hashes being hard-coded in the test are valid
SHA256 hashes.
Let’s test the merkleProof
function:
describe "### Crypto.Merkle.merkleProof" $ do
it "computes the merkle proof for a given Tx in a list of txs" $ do
let toHash = fromJust . parseSHA256
tx = toHash
"94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05"
txs = toHash <$>
[ "1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b"
, "94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05"
, "80a2726fbbe93a8a74bc5a357274510e6a00dfd50489a13c396d2c288e106ec2"
, "5a3e9111cc3a69cc26d290578d46fb40ba1d4abcf706487a1b6d03730d3bdf02"
]
expected =
[ Left $ toHash
"1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b"
, Right $ toHash
"913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435"
]
merkleProof txs tx `shouldBe` expected
Finally the verify
function to assure that a proof is valid and that using
such proof we arrive at the Merkle Root hash:
describe "### Crypto.Merkle.verify" $ do
it "verifies validity of Tx inclusion using the provided proof" $ do
let toHash = fromJust . parseSHA256
tx = toHash
"94d67aa1720ef6b58d130e39f3b7b4e5e7dab07698ab6baf1465e7e639115e05"
mkr = toHash
"74fe176dcfe07bf6e0ef0f9ee63c81b78623ac9b03137d5f4cfd80f0e500a7c3"
proof =
[ Left $ toHash
"1877fc02dfb78b83b913c0eef8fa5990a55dd4a56449faf97a0dcb6f04cff32b"
, Right $ toHash
"913489ac6c001574f5218a4d2d0de1d59258e663d2dfc0f091b6b302ae2cb435"
]
proof `shouldSatisfy` verify tx mkr
Conclusion
In this post we’ve introduced the algorithm used in bitcoin to compute the Merkle Root hash, a Merkle Proof used in Simplified Payment Verification (SPV) and finally verify integrity in the proof and use it to attest that the claim that some transaction X being in a block Y is indeed true. We did all of this while using Haskell and overall a good time exercising our functional muscles. Haskell is not only a research language, I believe it has potential to be widely adopted in industry, if only we’re willing to give it a shot.