Code Monkey home page Code Monkey logo

sparse-merkle-trees's Introduction

sparse-merkle-trees

CI/CD Hackage BSD3

A Haskell library implementing sparse Merkle trees, an authenticated data structure with support for zero-knowledge proofs of inclusion and exclusion, parametrised over cryptographic hash algorithms at the type level.

Note: This library is currently experimental and is subject to change.

Introduction

A Merkle tree is an authenticated data structure which supports efficient zero-knowledge proofs of element inclusion from a Merkle root.

A sparse Merkle tree (SMT) is Merkle Tree where all possible keys (digests) are at the leaves of the tree. This gives us the additional properties over a Merkle tree:

  • support for proofs of exclusion of elements from a Merkle root
  • history independence of the merkle root from element insertion order

A naive construction would mean that a N-bit key would yield a SMT of size 2^N. However, because the tree is sparse, there are efficient constructions that grow in size O(n) where n is the size of the tree.

Use cases

SMTs expand on the existing use cases of Merkle trees including:

  • Asset universes
  • Certificate revocation
  • Secure file systems
  • Secure messaging

Examples

Compact Sparse Merkle Trees

The compact sparse Merkle tree is based on the description given in this report by Faraz Haider. The module exposes an similar API to Data.Set but this is subject to change.

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}

import Crypto.Hash (SHA256) -- from cryptonite package
import Crypto.Hash.CompactSparseMerkleTree (CSMT, MembershipProof, MerkleRoot, Size (NonEmpty))
import qualified Crypto.Hash.CompactSparseMerkleTree as CSMT
import Data.ByteString (ByteString) -- from bytestring package

type MailingList = CSMT 'NonEmpty SHA256 ByteString

cypherPunks :: MailingList
cypherPunks =
  CSMT.insert "[email protected]" $
    CSMT.insert "[email protected]" $
      CSMT.insert "[email protected]" $
        CSMT.insert "[email protected]" $
          CSMT.insert "[email protected]" $
            CSMT.empty

summary :: MerkleRoot SHA256
summary = CSMT.merkleRoot cypherPunks

-- >>> summary
-- MerkleRoot b7061997fc49294bfb5c8893a684eea53d20f11d152530fbb95b3fc5ca902d2a

nakamotoProof :: MembershipProof SHA256
nakamotoProof = CSMT.membershipProof "[email protected]" cypherPunks

-- >>> nakamotoProof
-- MembershipProof (InclusionProof {includedDigest = 4a2220676a74d2be6d0c00d939513a3b5599bd01c65cf3d1ce2d517f070a1c11, rootPath = [(5554c052244897a83ef61362e6a3141c034284b54f4977163070d634749a714c,R),(6c98a4128b8a86d5f646707d860a869244938b95177298c6746da5e1e981426e,R),(e1a4e69d03cd197af06688aafb33d50db1d7c407be747b4b9d46c877f2e97fa1,R)]})

szaboTechbookProof :: MembershipProof SHA256
szaboTechbookProof = CSMT.membershipProof "[email protected]" cypherPunks

-- >>> szaboTechbookProof
-- MembershipProof (InclusionProof {includedDigest = 5554c052244897a83ef61362e6a3141c034284b54f4977163070d634749a714c, rootPath = [(4a2220676a74d2be6d0c00d939513a3b5599bd01c65cf3d1ce2d517f070a1c11,L),(6c98a4128b8a86d5f646707d860a869244938b95177298c6746da5e1e981426e,R),(e1a4e69d03cd197af06688aafb33d50db1d7c407be747b4b9d46c877f2e97fa1,R)]})

szaboNetcomProof :: MembershipProof SHA256
szaboNetcomProof = CSMT.membershipProof "[email protected]" cypherPunks

-- >>> szaboNetcomProof
-- MembershipProof (ExclusionProof {excludedDigest = 8f3af01ec764fa90a9bb98b1547656e362640fc336cf31c80b7dfacb50f2d256, immediatePredecessor = Just (InclusionProof {includedDigest = 6c98a4128b8a86d5f646707d860a869244938b95177298c6746da5e1e981426e, rootPath = [(0fa34cea30d143cb5bbfd6937e3848c8faf4d0737b88b55fbcb0f2afac94e6b3,())]}), immediateSuccessor = Just (InclusionProof {includedDigest = 949802fb7f855457ede853818031b82bc5f446c7369f7abe6fa9e564dde18e96, rootPath = [(dc2baa959e086c741627d36a0804a302590b11e44590936621e81acd4a528de4,())]}), commonRootPath = []})

cypherPunks' :: MailingList
cypherPunks' = CSMT.delete "[email protected]" (CSMT.insert "[email protected]" cypherPunks) $ \case
  t@CSMT.Parent {} -> t
  _ -> error "impossible"

summary' :: MerkleRoot SHA256
summary' = CSMT.merkleRoot cypherPunks'

-- >>> summary'
-- MerkleRoot 7dc6b4dfcd54f9c6ac67a330b35539407c2e9559d7e589e6064f1c8a46256aa7

szaboTechbookProof' :: MembershipProof SHA256
szaboTechbookProof' = CSMT.membershipProof "[email protected]" cypherPunks'

-- >>> szaboTechbookProof'
-- MembershipProof (ExclusionProof {excludedDigest = 5554c052244897a83ef61362e6a3141c034284b54f4977163070d634749a714c, immediatePredecessor = Just (InclusionProof {includedDigest = 4a2220676a74d2be6d0c00d939513a3b5599bd01c65cf3d1ce2d517f070a1c11, rootPath = []}), immediateSuccessor = Just (InclusionProof {includedDigest = 6c98a4128b8a86d5f646707d860a869244938b95177298c6746da5e1e981426e, rootPath = []}), commonRootPath = [(b8804f3bbe10963f35ee72dbd55a8aa33b64260ab0c63bff59acc13ea8088e56,R)]})

szaboNetcomProof' :: MembershipProof SHA256
szaboNetcomProof' = CSMT.membershipProof "[email protected]" cypherPunks'

-- >>> szaboNetcomProof
-- MembershipProof (ExclusionProof {excludedDigest = 8f3af01ec764fa90a9bb98b1547656e362640fc336cf31c80b7dfacb50f2d256, immediatePredecessor = Just (InclusionProof {includedDigest = 6c98a4128b8a86d5f646707d860a869244938b95177298c6746da5e1e981426e, rootPath = [(0fa34cea30d143cb5bbfd6937e3848c8faf4d0737b88b55fbcb0f2afac94e6b3,())]}), immediateSuccessor = Just (InclusionProof {includedDigest = 949802fb7f855457ede853818031b82bc5f446c7369f7abe6fa9e564dde18e96, rootPath = [(dc2baa959e086c741627d36a0804a302590b11e44590936621e81acd4a528de4,())]}), commonRootPath = []})

-- >>> all (CSMT.validProof summary) [nakamotoProof, szaboTechbookProof, szaboNetcomProof]
-- True
-- >>> all (CSMT.validProof summary') [szaboTechbookProof', szaboNetcomProof']
-- True
-- >>> CSMT.validProof summary' nakamotoProof
-- False

See the more complete haddock documentation on Hackage.

Related libraries

sparse-merkle-trees's People

Contributors

tochicool avatar

Stargazers

 avatar  avatar

Watchers

 avatar

sparse-merkle-trees's Issues

Is this still experimental?

The README and version number indicate this library is experimental. What would you say is missing to make this stable and relied upon?

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    ๐Ÿ–– Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. ๐Ÿ“Š๐Ÿ“ˆ๐ŸŽ‰

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google โค๏ธ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.