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

Copyright2018 DFINITY Stiftung
LicenseGPL-3
MaintainerEnzo Haussecker <enzo@dfinity.org>
StabilityStable
Safe HaskellNone
LanguageHaskell2010

DFINITY.RadixTree

Contents

Description

A generic data integrity layer.

Synopsis

Class

class Monad m => RadixDatabase m database where Source #

Minimal complete definition

load, store

Methods

load :: database -> ByteString -> m (Maybe ByteString) Source #

store :: database -> ByteString -> ByteString -> m () Source #

Instances
MonadIO m => RadixDatabase m DB Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Methods

load :: DB -> ByteString -> m (Maybe ByteString) Source #

store :: DB -> ByteString -> ByteString -> m () Source #

MonadIO m => RadixDatabase m (IORef (Map ByteString ByteString)) Source # 
Instance details

Defined in DFINITY.RadixTree.Types

RadixDatabase (ST s) (STRef s (Map ByteString ByteString)) Source # 
Instance details

Defined in DFINITY.RadixTree.Types

RadixDatabase (Transaction ReadWrite) (Database ByteString ByteString) Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Monad m => RadixDatabase (StateT (Map ByteString ByteString) m) () Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Types

data RadixError Source #

Instances
Eq RadixError Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Data RadixError Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RadixError -> c RadixError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RadixError #

toConstr :: RadixError -> Constr #

dataTypeOf :: RadixError -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RadixError) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RadixError) #

gmapT :: (forall b. Data b => b -> b) -> RadixError -> RadixError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RadixError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RadixError -> r #

gmapQ :: (forall d. Data d => d -> u) -> RadixError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RadixError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RadixError -> m RadixError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixError -> m RadixError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixError -> m RadixError #

Show RadixError Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Exception RadixError Source # 
Instance details

Defined in DFINITY.RadixTree.Types

data RadixProof Source #

Instances
Eq RadixProof Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Data RadixProof Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RadixProof -> c RadixProof #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RadixProof #

toConstr :: RadixProof -> Constr #

dataTypeOf :: RadixProof -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RadixProof) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RadixProof) #

gmapT :: (forall b. Data b => b -> b) -> RadixProof -> RadixProof #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RadixProof -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RadixProof -> r #

gmapQ :: (forall d. Data d => d -> u) -> RadixProof -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RadixProof -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RadixProof -> m RadixProof #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixProof -> m RadixProof #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RadixProof -> m RadixProof #

Show RadixProof Source # 
Instance details

Defined in DFINITY.RadixTree.Types

NFData RadixProof Source # 
Instance details

Defined in DFINITY.RadixTree.Types

Methods

rnf :: RadixProof -> () #

Serialise RadixProof Source # 
Instance details

Defined in DFINITY.RadixTree.Types

data RadixTree database Source #

Getters

Create

createRadixTree Source #

Arguments

:: RadixDatabase m database 
=> Int

Bloom filter size in bits.

-> Int

LRU cache size in items.

-> Maybe RadixRoot

Previous state root.

-> database

Database.

-> m (RadixTree database) 

Create a radix tree.

Insert

insertRadixTree Source #

Arguments

:: RadixDatabase m database 
=> ByteString

Key.

-> ByteString

Value.

-> RadixTree database

Radix tree.

-> m (RadixTree database) 

Insert a value into a radix tree.

Delete

deleteRadixTree Source #

Arguments

:: RadixDatabase m database 
=> ByteString

Key.

-> RadixTree database

Radix tree.

-> m (RadixTree database) 

Delete a value from a radix tree.

Merkleize

merkleizeRadixTree Source #

Arguments

:: RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m (RadixRoot, RadixTree database) 

Merkleize a radix tree. This will flush the buffer to the database.

Query

lookupRadixTree Source #

Arguments

:: RadixDatabase m database 
=> ByteString

Key.

-> RadixTree database

Radix tree.

-> m (Maybe (ByteString, RadixTree database)) 

Lookup a value in a radix tree.

Prove

createRadixProof Source #

Arguments

:: RadixDatabase m database 
=> ByteString

Key.

-> RadixTree database

Radix tree.

-> m (Maybe (RadixProof, RadixTree database)) 

Prove that a value exists in a radix tree.

Verify

verifyRadixProof Source #

Arguments

:: ByteString

Key.

-> RadixRoot

State root.

-> RadixProof

Radix proof.

-> Bool 

Verify that a value exists in a radix tree.

Test

isEmptyRadixTree Source #

Arguments

:: RadixTree database

Radix tree.

-> Bool 

Check if a radix tree is empty.

isValidRadixRoot Source #

Arguments

:: RadixDatabase m database 
=> RadixRoot

State root.

-> RadixTree database

Radix tree.

-> m Bool 

Check if a state root is valid.

Debug

Contents

contentsRadixTree Source #

Arguments

:: RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m [(ByteString, ByteString)] 

A convenient alias for contentsNonMerkleizedRadixTree.

contentsMerkleizedRadixTree Source #

Arguments

:: RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m [(ByteString, ByteString)] 

Get the contents of a Merkleized radix tree.

contentsNonMerkleizedRadixTree Source #

Arguments

:: RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m [(ByteString, ByteString)] 

Get the contents of a non-Merkleized radix tree.

Print

printRadixTree Source #

Arguments

:: MonadIO m 
=> RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m () 

A convenient alias for printNonMerkleizedRadixTree.

printMerkleizedRadixTree Source #

Arguments

:: MonadIO m 
=> RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m () 

Print a Merkleized radix tree.

printNonMerkleizedRadixTree Source #

Arguments

:: MonadIO m 
=> RadixDatabase m database 
=> RadixTree database

Radix tree.

-> m () 

Print a non-Merkleized radix tree.