Copyright | 2018 DFINITY Stiftung |
---|---|
License | GPL-3 |
Maintainer | Enzo Haussecker <enzo@dfinity.org> |
Stability | Stable |
Safe Haskell | None |
Language | Haskell2010 |
A generic data integrity layer.
Synopsis
- class Monad m => RadixDatabase config m database | database -> config where
- data RadixError
- type RadixRoot = ShortByteString
- data RadixTree database
- createRadixTree :: RadixDatabase config m database => Int -> Int -> Maybe RadixRoot -> config -> m (RadixTree database)
- subtreeRadixTree :: RadixDatabase config m database => RadixRoot -> RadixTree database -> m (RadixTree database)
- insertRadixTree :: RadixDatabase config m database => ByteString -> ByteString -> RadixTree database -> m (RadixTree database)
- deleteRadixTree :: RadixDatabase config m database => ByteString -> RadixTree database -> m (RadixTree database)
- merkleizeRadixTree :: RadixDatabase config m database => RadixTree database -> m (RadixRoot, RadixTree database)
- lookupRadixTree :: RadixDatabase config m database => ByteString -> RadixTree database -> m (Maybe (ByteString, RadixTree database))
- lookupMerkleizedRadixTree :: RadixDatabase config m database => ByteString -> RadixTree database -> m (Maybe (ByteString, RadixTree database))
- lookupNonMerkleizedRadixTree :: RadixDatabase config m database => ByteString -> RadixTree database -> m (Maybe (ByteString, RadixTree database))
- isEmptyRadixTree :: RadixTree database -> Bool
- isValidRadixRoot :: RadixDatabase config m database => RadixRoot -> RadixTree database -> m Bool
- sourceMerkleizedRadixTree :: MonadResource m => RadixDatabase config (ConduitM () ByteString m) database => [Bool] -> Int -> BoundedChan RadixRoot -> RadixTree database -> ConduitM () ByteString m ()
- sinkMerkleizedRadixTree :: MonadResource m => RadixDatabase config (ConduitM ByteString () m) database => RadixRoot -> BoundedChan RadixRoot -> RadixTree database -> ConduitM ByteString () m (Either [RadixRoot] (RadixTree database))
- contentsRadixTree :: RadixDatabase config m database => RadixTree database -> m [(ByteString, ByteString)]
- contentsMerkleizedRadixTree :: RadixDatabase config m database => RadixTree database -> m [(ByteString, ByteString)]
- contentsNonMerkleizedRadixTree :: RadixDatabase config m database => RadixTree database -> m [(ByteString, ByteString)]
- printRadixTree :: MonadIO m => RadixDatabase config m database => RadixTree database -> m ()
- printMerkleizedRadixTree :: MonadIO m => RadixDatabase config m database => RadixTree database -> m ()
- printNonMerkleizedRadixTree :: MonadIO m => RadixDatabase config m database => RadixTree database -> m ()
Class
class Monad m => RadixDatabase config m database | database -> config where Source #
create :: config -> m database Source #
load :: database -> ByteString -> m (Maybe ByteString) Source #
store :: database -> ByteString -> ByteString -> m () Source #
Instances
Monad m => RadixDatabase () (StateT (Map ByteString ByteString) m) () Source # | |
Defined in Network.DFINITY.RadixTree.Types create :: () -> StateT (Map ByteString ByteString) m () Source # load :: () -> ByteString -> StateT (Map ByteString ByteString) m (Maybe ByteString) Source # store :: () -> ByteString -> ByteString -> StateT (Map ByteString ByteString) m () Source # | |
MonadResource m => RadixDatabase (FilePath, Options) m DB Source # | |
Defined in Network.DFINITY.RadixTree.Types create :: (FilePath, Options) -> m DB Source # load :: DB -> ByteString -> m (Maybe ByteString) Source # store :: DB -> ByteString -> ByteString -> m () Source # |
Types
data RadixError Source #
Instances
type RadixRoot = ShortByteString Source #
Create
:: RadixDatabase config m database | |
=> Int | Bloom filter size in bits. |
-> Int | LRU cache size in items. |
-> Maybe RadixRoot | Previous state root. |
-> config | Database configuration. |
-> m (RadixTree database) |
Create a radix tree.
:: RadixDatabase config m database | |
=> RadixRoot | State root. |
-> RadixTree database | Radix tree. |
-> m (RadixTree database) |
Create a radix tree from a radix tree.
Insert
:: RadixDatabase config m database | |
=> ByteString | Key. |
-> ByteString | Value. |
-> RadixTree database | Radix tree. |
-> m (RadixTree database) |
Insert a key and value into a radix tree.
Delete
:: RadixDatabase config m database | |
=> ByteString | Key. |
-> RadixTree database | Radix tree. |
-> m (RadixTree database) |
Delete a value from a radix tree.
Merkleize
:: RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m (RadixRoot, RadixTree database) |
Merkleize a radix tree. This will flush the buffer to disk.
Query
:: RadixDatabase config m database | |
=> ByteString | Key. |
-> RadixTree database | Radix tree. |
-> m (Maybe (ByteString, RadixTree database)) |
A convenient alias for lookupNonMerkleizedRadixTree
.
lookupMerkleizedRadixTree Source #
:: RadixDatabase config m database | |
=> ByteString | Key. |
-> RadixTree database | Radix tree. |
-> m (Maybe (ByteString, RadixTree database)) |
Lookup a value in a Merkleized radix tree.
lookupNonMerkleizedRadixTree Source #
:: RadixDatabase config m database | |
=> ByteString | Key. |
-> RadixTree database | Radix tree. |
-> m (Maybe (ByteString, RadixTree database)) |
Lookup a value in a non-Merkleized radix tree.
Test
:: RadixDatabase config m database | |
=> RadixRoot | State root. |
-> RadixTree database | Radix tree. |
-> m Bool |
Check if a state root is valid.
Stream
sourceMerkleizedRadixTree Source #
:: MonadResource m | |
=> RadixDatabase config (ConduitM () ByteString m) database | |
=> [Bool] | Bit mask. |
-> Int | LRU cache size in items. |
-> BoundedChan RadixRoot | Terminal state root producer. |
-> RadixTree database | Radix tree. |
-> ConduitM () ByteString m () |
Create a conduit from a Merkleized radix tree.
sinkMerkleizedRadixTree Source #
:: MonadResource m | |
=> RadixDatabase config (ConduitM ByteString () m) database | |
=> RadixRoot | Target state root. |
-> BoundedChan RadixRoot | Terminal state root consumer. |
-> RadixTree database | Radix tree. |
-> ConduitM ByteString () m (Either [RadixRoot] (RadixTree database)) |
Create a Merkleized radix tree from a conduit.
Debug
:: RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m [(ByteString, ByteString)] |
A convenient alias for contentsNonMerkleizedRadixTree
.
contentsMerkleizedRadixTree Source #
:: RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m [(ByteString, ByteString)] |
Get the contents of a Merkleized radix tree.
contentsNonMerkleizedRadixTree Source #
:: RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m [(ByteString, ByteString)] |
Get the contents of a non-Merkleized radix tree.
:: MonadIO m | |
=> RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m () |
A convenient alias for printNonMerkleizedRadixTree
.
printMerkleizedRadixTree Source #
:: MonadIO m | |
=> RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m () |
Print a Merkleized radix tree.
printNonMerkleizedRadixTree Source #
:: MonadIO m | |
=> RadixDatabase config m database | |
=> RadixTree database | Radix tree. |
-> m () |
Print a non-Merkleized radix tree.