dfinity-radix-tree: A generic data integrity layer.

[ blockchain, bsd3, database, dfinity, library, program ] [ Propose Tags ]

This library allows you to construct a Merkle tree on top of any underlying key–value database. It works by organizing your key–value pairs into a binary radix tree, which is well suited for storing large dictionaries of fairly random keys, and is optimized for storing keys of the same length.


[Skip to Readme]

Modules

[Last Documentation]

  • DFINITY
    • DFINITY.RadixTree
      • DFINITY.RadixTree.Conduit

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.0.0, 0.1.0, 0.1.1, 0.2.0, 0.2.1, 0.3.0, 0.3.1, 0.4.0, 0.5.0, 0.5.1, 0.5.2, 0.6.0, 0.6.1, 0.6.2, 0.6.3
Change log CHANGELOG.md
Dependencies base (>=4.10 && <5), base16-bytestring, BoundedChan, bytestring, concurrent-extra, conduit, containers, cryptonite, data-default-class, deepseq, dfinity-radix-tree, directory, dlist, hashtables, lens-simple, leveldb-haskell, lrucaching, memory, mtl, reducers, resourcet, serialise, temporary, transformers [details]
License BSD-3-Clause
Copyright 2018-2019 DFINITY Stiftung
Author Enzo Haussecker <enzo@dfinity.org>, Remy Goldschmidt <remy@dfinity.org>, Armando Ramirez <armando@dfinity.org>
Maintainer Enzo Haussecker <enzo@dfinity.org>, Remy Goldschmidt <remy@dfinity.org>, Armando Ramirez <armando@dfinity.org>
Category Blockchain, DFINITY, Database
Home page https://dfinity.org
Uploaded by EnzoHaussecker at 2019-03-14T07:50:50Z
Distributions
Executables dfinity-radix-tree-example
Downloads 8032 total (32 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs not available [build log]
All reported builds failed as of 2019-03-14 [all 2 reports]

Readme for dfinity-radix-tree-0.6.3

[back to package description]

dfinity-radix-tree: A generic data integrity layer.

DFINITY Hackage Dependencies License: BSD 3-Clause

Overview

This library allows you to construct a Merkle tree on top of any underlying key-value database. It works by organizing your key-value pairs into a binary radix tree, which is well suited for storing large dictionaries of fairly random keys, and is optimized for storing keys of the same length.

Usage

Define your database as an instance of the RadixDatabase type class. An instance for LevelDB is already provided.

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

import Control.Monad.IO.Class (MonadIO)
import Database.LevelDB (DB, defaultReadOptions, defaultWriteOptions, get, put)

import DFINITY.RadixTree

instance MonadIO m => RadixDatabase m DB where
  load database = get database defaultReadOptions
  store database = put database defaultWriteOptions

Create a RadixTree that is parameterized by your database. If you want to make things more explicit, then you can define a simple type alias and wrapper function.

import Control.Monad.Trans.Resource (MonadResource)
import Database.LevelDB (DB, Options(..), defaultOptions, open)

import DFINITY.RadixTree

type RadixTree' = RadixTree DB

createRadixTree'
  :: MonadResource m
  => FilePath -- Database.
  -> Maybe RadixRoot -- State root.
  -> m RadixTree'
createRadixTree' file root = do
  handle <- open file options
  createRadixTree cacheSize root handle
  where
  cacheSize = 2048
  options   = defaultOptions { createIfMissing = True }

Using the definitions above, you can create a radix tree, perform some basic operations on it, and see that its contents is uniquely defined by its RadixRoot.

{-# LANGUAGE OverloadedStrings #-}

import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Resource (runResourceT)
import Data.ByteString.Base16 (encode)
import Data.ByteString.Char8 (unpack)
import Data.ByteString.Short (fromShort)

import DFINITY.RadixTree

main :: IO ()
main = runResourceT $ do

  -- Create a radix tree, insert a key-value pair, and Merkleize.
  tree  <- createRadixTree' "/path/to/database" Nothing
  tree' <- insertRadixTree "Hello" "World" tree
  root  <- fst <$> merkleizeRadixTree tree'

  -- Print the state root.
  liftIO $ putStrLn $ "State Root: 0x" ++ pretty root
  where pretty = unpack . encode . fromShort

Running the program above should produce the following result.

State Root: 0xb638755216858bc84de8b80f480f15ca5c733e95

License

dfinity-radix-tree is licensed under the BSD 3-Clause License.