@hackage dfinity-radix-tree0.1.1

A generic data integrity layer.

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

Build Status Hackage Dependencies License: GPLv3

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.Trans.Resource (MonadResource)
import Database.LevelDB (DB, Options, defaultReadOptions, defaultWriteOptions, get, open, put)

import Network.DFINITY.RadixTree

instance MonadResource m => RadixDatabase (FilePath, Options) m DB where
   create = uncurry open
   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)

import Network.DFINITY.RadixTree

type RadixTree' = RadixTree DB

createRadixTree'
   :: MonadResource m
   => FilePath -- Database.
   -> Maybe RadixRoot -- State root.
   -> m RadixTree'
createRadixTree' path root =
   createRadixTree bloomSize cacheSize root (path, options)
   where
   bloomSize = 262144
   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 Network.DFINITY.RadixTree

main :: IO ()
main = runResourceT $ do
   tree  <- createRadixTree' "/path/to/database" Nothing
   tree' <- insertRadixTree "Hello" "World" tree
   root  <- fst <$> merkleizeRadixTree tree'
   liftIO $ putStrLn $ "State Root: 0x" ++ pretty root
   where pretty = unpack . encode . fromShort

Running the program above should produce the following result.

State Root: 0x621f6e4c28b18e58d374c9236daa1a0ccba16550

Contribute

Feel free to join in. All are welcome. Open an issue!

License

GPLv3