{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS -Wall #-}
{-# OPTIONS -fno-warn-incomplete-patterns #-}
module Network.DFINITY.RadixTree (
RadixRoot
, RadixTree
, RadixError(..)
, createRadixTree
, subtreeRadixTree
, insertRadixTree
, deleteRadixTree
, merkleizeRadixTree
, lookupMerkleizedRadixTree
, lookupNonMerkleizedRadixTree
, isEmptyRadixTree
, isValidRadixRoot
, sourceMerkleizedRadixTree
, printMerkleizedRadixTree
, printNonMerkleizedRadixTree
) where
import Codec.Serialise (deserialise)
import Control.Concurrent (forkIO, killThread)
import Control.Concurrent.BoundedChan (BoundedChan, readChan)
import Control.Concurrent.MVar (modifyMVar_, newMVar, readMVar)
import Control.Exception (throw)
import Control.Monad (forM_, forever, when)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Resource (MonadResource, ResourceT, allocate, release)
import Data.BloomFilter as Bloom (elem, insert, insertList)
import Data.Bool (bool)
import Data.ByteString.Char8 (ByteString)
import Data.ByteString.Lazy (fromStrict)
import Data.ByteString.Short (fromShort)
import Data.Conduit (Source, yield)
import Data.Default.Class (def)
import Data.List.NonEmpty (NonEmpty(..), fromList)
import Data.LruCache as LRU (empty, insert, lookup)
import Data.Map.Strict as Map (empty)
import Data.Maybe (fromJust, isJust, isNothing, listToMaybe)
import Data.Tuple (swap)
import Database.LevelDB (Options(..), defaultReadOptions, get, open)
import Network.DFINITY.RadixTree.Bits
import Network.DFINITY.RadixTree.Bloom
import Network.DFINITY.RadixTree.Lenses
import Network.DFINITY.RadixTree.Memory
import Network.DFINITY.RadixTree.Types
import Network.DFINITY.RadixTree.Utilities
createRadixTree
:: MonadResource m
=> Int
-> Int
-> FilePath
-> Maybe RadixRoot
-> m RadixTree
{-# SPECIALISE createRadixTree
:: Int
-> Int
-> FilePath
-> Maybe RadixRoot
-> ResourceT IO RadixTree #-}
createRadixTree bloomSize cacheSize file checkpoint
| bloomSize <= 0 = throw $ InvalidArgument "invalid Bloom filter size"
| cacheSize <= 0 = throw $ InvalidArgument "invalid LRU cache size"
| otherwise = do
database <- open file $ def {createIfMissing = True}
(root, cache') <-
case checkpoint of
Nothing -> storeCold def cache database
Just root -> do
result <- loadCold root cache database
case snd <$> result of
Nothing -> throw $ StateRootDoesNotExist root
Just cache' -> pure (root, cache')
pure $ RadixTree bloom bloomSize Map.empty cache' cacheSize root database root
where
bloom = emptyRadixBloom bloomSize
cache = LRU.empty cacheSize
subtreeRadixTree
:: MonadIO m
=> RadixRoot
-> RadixTree
-> m RadixTree
{-# SPECIALISE subtreeRadixTree
:: RadixRoot
-> RadixTree
-> ResourceT IO RadixTree #-}
subtreeRadixTree root RadixTree {..} = do
result <- loadCold root cache _radixDatabase
case result of
Nothing -> throw $ StateRootDoesNotExist root
_ -> pure $ RadixTree bloom _radixBloomSize Map.empty cache _radixCacheSize root _radixDatabase root
where
bloom = emptyRadixBloom _radixBloomSize
cache = LRU.empty _radixCacheSize
isEmptyRadixTree
:: RadixTree
-> Bool
{-# INLINE isEmptyRadixTree #-}
isEmptyRadixTree = (==) defaultRoot . _radixRoot
isValidRadixRoot
:: MonadIO m
=> RadixRoot
-> RadixTree
-> m Bool
{-# SPECIALISE isValidRadixRoot
:: RadixRoot
-> RadixTree
-> ResourceT IO Bool #-}
isValidRadixRoot root RadixTree {..} =
isJust <$> get _radixDatabase defaultReadOptions key
where
key = fromShort root
searchRadixTree
:: MonadIO m
=> Bool
-> (RadixTree -> m (Maybe (RadixBranch, RadixCache)))
-> ByteString
-> RadixTree
-> m (Either RadixError RadixSearchResult)
{-# SPECIALISE searchRadixTree
:: Bool
-> (RadixTree -> ResourceT IO (Maybe (RadixBranch, RadixCache)))
-> ByteString
-> RadixTree
-> ResourceT IO (Either RadixError RadixSearchResult) #-}
searchRadixTree flag load = \ key tree@RadixTree {..} -> do
let key' = toBits key
let tree' = tree `bool` setRoot _radixCheckpoint tree $ flag
loop Nothing [] [] [] key' tree' where
loop implicit branches roots prefixes key tree@RadixTree {..} = do
result <- load tree
case result of
Nothing -> pure $ Left $ StateRootDoesNotExist _radixRoot
Just (branch@RadixBranch {..}, cache') -> do
let bits = maybe id (:) implicit $ maybe [] toBits _radixPrefix
let prefix = matchBits bits key
let n = length prefix
let overflow = drop n bits
let roots' = _radixRoot:roots
let branches' = branch:branches
let prefixes' = prefix:prefixes
let key' = drop n key
let residue = not $ null overflow
let bit = head key'
let child = bool _radixLeft _radixRight bit
if null key' || residue || isNothing child
then pure $ Right (fromList roots', fromList branches', fromList prefixes', overflow, key', cache')
else do
let root' = fromJust child
let tree' = setCache cache' $ setRoot root' tree
let implicit' = Just bit
loop implicit' branches' roots' prefixes' key' tree'
searchMerkleizedRadixTree
:: MonadIO m
=> ByteString
-> RadixTree
-> m (Either RadixError RadixSearchResult)
{-# SPECIALISE searchMerkleizedRadixTree
:: ByteString
-> RadixTree
-> ResourceT IO (Either RadixError RadixSearchResult) #-}
searchMerkleizedRadixTree =
searchRadixTree True $ \ RadixTree {..} ->
loadCold _radixRoot _radixCache _radixDatabase
searchNonMerkleizedRadixTree
:: MonadIO m
=> ByteString
-> RadixTree
-> m (Either RadixError RadixSearchResult)
{-# SPECIALISE searchNonMerkleizedRadixTree
:: ByteString
-> RadixTree
-> ResourceT IO (Either RadixError RadixSearchResult) #-}
searchNonMerkleizedRadixTree =
searchRadixTree False $ \ RadixTree {..} ->
loadHot _radixRoot _radixBuffer _radixCache _radixDatabase
insertRadixTree
:: MonadIO m
=> ByteString
-> ByteString
-> RadixTree
-> m RadixTree
{-# SPECIALISE insertRadixTree
:: ByteString
-> ByteString
-> RadixTree
-> ResourceT IO RadixTree #-}
insertRadixTree key value tree =
if isEmptyRadixTree tree
then pure $ initializeRadixTree key value tree
else searchNonMerkleizedRadixTree key tree >>= \ case
Left err -> throw err
Right result@(_, _, _, [], [], _) ->
pure $ insertRadixTreeAt result value tree
Right result@(_, _, _, [], _, _) ->
pure $ insertRadixTreeAfter result value tree
Right result@(_, _, _, _, [], _) ->
pure $ insertRadixTreeBefore result value tree
Right result ->
pure $ insertRadixTreeBetween result value tree
initializeRadixTree
:: ByteString
-> ByteString
-> RadixTree
-> RadixTree
{-# INLINE initializeRadixTree #-}
initializeRadixTree key value tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setRoot root tree
where
prefix = createPrefix $ toBits key
branch = setPrefix prefix $ Just value `setLeaf` def
root = createRoot branch
bloom = Bloom.insert root _radixBloom
buffer = storeHot root branch _radixBuffer
insertRadixTreeAt
:: RadixSearchResult
-> ByteString
-> RadixTree
-> RadixTree
{-# INLINE insertRadixTreeAt #-}
insertRadixTreeAt (_:|roots, branch:|branches, prefix:|_, _, _, cache) value tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
branch' = Just value `setLeaf` branch
root' = createRoot branch'
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root':roots
buffer = merkleSpoof root' parent $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root' $ isNothing parent
insertRadixTreeAfter
:: RadixSearchResult
-> ByteString
-> RadixTree
-> RadixTree
{-# INLINE insertRadixTreeAfter #-}
insertRadixTreeAfter (_:|roots, branch:|branches, prefix:|_, _, keyOverflow, cache) value tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
prefix' = createPrefix $ drop 1 keyOverflow
branch' = setPrefix prefix' $ Just value `setLeaf` def
root' = createRoot branch'
branch'' = test `setChild` Just root' $ branch
root'' = createRoot branch''
test = head keyOverflow
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root'':root':roots
buffer = merkleSpoof root'' parent $ storeHot root'' branch'' $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root'' $ isNothing parent
insertRadixTreeBefore
:: RadixSearchResult
-> ByteString
-> RadixTree
-> RadixTree
{-# INLINE insertRadixTreeBefore #-}
insertRadixTreeBefore (_:|roots, branch:|branches, prefix:|_, prefixOverflow, _, cache) value tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
prefix' = createPrefix $ drop 1 prefixOverflow
branch' = setPrefix prefix' branch
root' = createRoot branch'
prefix'' = createPrefix $ drop 1 prefix `bool` prefix $ isNothing parent
branch'' = setPrefix prefix'' $ test `setChild` Just root' $ Just value `setLeaf` def
root'' = createRoot branch''
test = head prefixOverflow
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root'':root':roots
buffer = merkleSpoof root'' parent $ storeHot root'' branch'' $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root'' $ isNothing parent
insertRadixTreeBetween
:: RadixSearchResult
-> ByteString
-> RadixTree
-> RadixTree
{-# INLINE insertRadixTreeBetween #-}
insertRadixTreeBetween (_:|roots, branch:|branches, prefix:|_, prefixOverflow, keyOverflow, cache) value tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
prefix' = createPrefix $ drop 1 keyOverflow
branch' = setPrefix prefix' $ Just value `setLeaf` def
root' = createRoot branch'
prefix'' = createPrefix $ drop 1 prefixOverflow
branch'' = setPrefix prefix'' branch
root'' = createRoot branch''
prefix''' = createPrefix $ drop 1 prefix `bool` prefix $ isNothing parent
branch''' = setPrefix prefix''' $ setChildren children def
root''' = createRoot branch'''
test = head keyOverflow
children = bool id swap test (Just root', Just root'')
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root''':root'':root':roots
buffer = merkleSpoof root''' parent $ storeHot root''' branch''' $ storeHot root'' branch'' $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root''' $ isNothing parent
deleteRadixTree
:: MonadIO m
=> ByteString
-> RadixTree
-> m RadixTree
{-# SPECIALISE deleteRadixTree
:: ByteString
-> RadixTree
-> ResourceT IO RadixTree #-}
deleteRadixTree key tree@RadixTree {..} =
if isEmptyRadixTree tree
then pure tree
else searchNonMerkleizedRadixTree key tree >>= \ case
Left err -> throw err
Right result@(_, branches, prefix:|_, [], [], cache) ->
case branches of
RadixBranch _ Nothing Nothing _:|[] ->
pure $ deleteRadixTreeNoChildrenNoParent result tree
RadixBranch _ Nothing Nothing _:|parent:_ | isJust $ getLeaf parent ->
pure $ deleteRadixTreeNoChildrenParentWithLeaf result tree
RadixBranch _ Nothing Nothing _:|parent:_ -> do
let test = not $ head prefix
let root = fromJust $ getChild test parent
loadHot root _radixBuffer cache _radixDatabase >>= \ case
Nothing -> throw $ StateRootDoesNotExist root
Just (branch, cache') ->
pure $ deleteRadixTreeNoChildrenParentWithoutLeaf result branch cache' test tree
RadixBranch _ child Nothing _:|_ | isJust child -> do
let test = False
let root = fromJust child
loadHot root _radixBuffer cache _radixDatabase >>= \ case
Nothing -> throw $ StateRootDoesNotExist root
Just (branch, cache') ->
pure $ deleteRadixTreeOneChild result branch cache' test tree
RadixBranch _ Nothing child _:|_ | isJust child -> do
let test = True
let root = fromJust child
loadHot root _radixBuffer cache _radixDatabase >>= \ case
Nothing -> throw $ StateRootDoesNotExist root
Just (branch, cache') ->
pure $ deleteRadixTreeOneChild result branch cache' test tree
_ -> pure $ deleteRadixTreeTwoChildren result tree
Right _ -> pure tree
deleteRadixTreeNoChildrenNoParent
:: RadixSearchResult
-> RadixTree
-> RadixTree
{-# INLINE deleteRadixTreeNoChildrenNoParent #-}
deleteRadixTreeNoChildrenNoParent (_, _, _, _, _, cache) tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
bloom = Bloom.insert defaultRoot _radixBloom
buffer = storeHot defaultRoot def _radixBuffer
state = defaultRoot
deleteRadixTreeNoChildrenParentWithLeaf
:: RadixSearchResult
-> RadixTree
-> RadixTree
{-# INLINE deleteRadixTreeNoChildrenParentWithLeaf #-}
deleteRadixTreeNoChildrenParentWithLeaf (_:|_:roots, _:|branch:branches, prefix:|prefixes, _, _, cache) tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
branch' = setChild test Nothing branch
root' = createRoot branch'
test = head prefix
parent = listToMaybe $ zip3 roots branches $ map head prefixes
bloom = flip insertList _radixBloom $ root':roots
buffer = merkleSpoof root' parent $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root' $ isNothing parent
deleteRadixTreeNoChildrenParentWithoutLeaf
:: RadixSearchResult
-> RadixBranch
-> RadixCache
-> Bool
-> RadixTree
-> RadixTree
{-# INLINE deleteRadixTreeNoChildrenParentWithoutLeaf #-}
deleteRadixTreeNoChildrenParentWithoutLeaf (_:|_:roots, _:|_:branches, _:|prefixes, _, _, _) branch@RadixBranch {..} cache test tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
prefix' = createPrefix $ drop 1 bits `bool` bits $ isNothing parent
branch' = setPrefix prefix' branch
root' = createRoot branch'
bits = head prefixes ++ test:maybe [] toBits _radixPrefix
parent = listToMaybe $ zip3 roots branches $ map head prefixes
bloom = flip insertList _radixBloom $ root':roots
buffer = merkleSpoof root' parent $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root' $ isNothing parent
deleteRadixTreeOneChild
:: RadixSearchResult
-> RadixBranch
-> RadixCache
-> Bool
-> RadixTree
-> RadixTree
{-# INLINE deleteRadixTreeOneChild #-}
deleteRadixTreeOneChild (_:|roots, _:|branches, prefix:|_, _, _, _) branch@RadixBranch {..} cache test tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
prefix' = createPrefix $ drop 1 bits `bool` bits $ isNothing parent
branch' = setPrefix prefix' branch
root' = createRoot branch'
bits = prefix ++ test:maybe [] toBits _radixPrefix
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root':roots
buffer = merkleSpoof root' parent $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root' $ isNothing parent
deleteRadixTreeTwoChildren
:: RadixSearchResult
-> RadixTree
-> RadixTree
{-# INLINE deleteRadixTreeTwoChildren #-}
deleteRadixTreeTwoChildren (_:|roots, branch:|branches, prefix:|_, _, _, cache) tree@RadixTree {..} =
seq bloom $ setBloom bloom $ setBuffer buffer $ setCache cache $ setRoot state tree
where
branch' = setLeaf Nothing branch
root' = createRoot branch'
parent = listToMaybe $ zip3 roots branches prefix
bloom = flip insertList _radixBloom $ root':roots
buffer = merkleSpoof root' parent $ storeHot root' branch' _radixBuffer
state = bool _radixRoot root' $ isNothing parent
lookupRadixTree
:: MonadIO m
=> (ByteString -> RadixTree -> m (Either RadixError RadixSearchResult))
-> ByteString
-> RadixTree
-> m (Maybe (ByteString, RadixTree))
{-# SPECIALISE lookupRadixTree
:: (ByteString -> RadixTree -> ResourceT IO (Either RadixError RadixSearchResult))
-> ByteString
-> RadixTree
-> ResourceT IO (Maybe (ByteString, RadixTree)) #-}
lookupRadixTree search key tree = do
found <- search key tree
case found of
Left err -> throw err
Right (_, RadixBranch {..}:|_, _, prefixOverflow, keyOverflow, cache') ->
if not $ null prefixOverflow && null keyOverflow
then pure Nothing
else pure $ do
value <- _radixLeaf
let tree' = setCache cache' tree
pure (value, tree')
lookupMerkleizedRadixTree
:: MonadIO m
=> ByteString
-> RadixTree
-> m (Maybe (ByteString, RadixTree))
{-# SPECIALISE lookupMerkleizedRadixTree
:: ByteString
-> RadixTree
-> ResourceT IO (Maybe (ByteString, RadixTree)) #-}
lookupMerkleizedRadixTree = lookupRadixTree searchMerkleizedRadixTree
lookupNonMerkleizedRadixTree
:: MonadIO m
=> ByteString
-> RadixTree
-> m (Maybe (ByteString, RadixTree))
{-# SPECIALISE lookupNonMerkleizedRadixTree
:: ByteString
-> RadixTree
-> ResourceT IO (Maybe (ByteString, RadixTree)) #-}
lookupNonMerkleizedRadixTree = lookupRadixTree searchNonMerkleizedRadixTree
merkleSpoof
:: RadixRoot
-> Maybe (RadixRoot, RadixBranch, Bool)
-> RadixBuffer
-> RadixBuffer
{-# INLINE merkleSpoof #-}
merkleSpoof mask = \ case
Nothing -> id
Just (root, branch, test) ->
storeHot root $ test `setChild` Just mask $ branch
merkleizeRadixTree
:: MonadIO m
=> RadixTree
-> m (RadixRoot, RadixTree)
{-# SPECIALISE merkleizeRadixTree
:: RadixTree
-> ResourceT IO (RadixRoot, RadixTree) #-}
merkleizeRadixTree RadixTree {..} = do
(root, cache) <- loop _radixRoot _radixCache
let tree = RadixTree bloom _radixBloomSize Map.empty cache _radixCacheSize root _radixDatabase root
pure (root, tree)
where
bloom = emptyRadixBloom _radixBloomSize
loop root cache =
if not $ Bloom.elem root _radixBloom
then pure (root, cache)
else do
result <- loadHot root _radixBuffer cache _radixDatabase
case result of
Nothing -> throw $ StateRootDoesNotExist root
Just (branch@RadixBranch {..}, cache') ->
case (_radixLeft, _radixRight) of
(Nothing, Nothing) ->
storeCold branch cache' _radixDatabase
(Just child, Nothing) -> do
(root', cache'') <- loop child cache'
let branch' = False `setChild` Just root' $ branch
storeCold branch' cache'' _radixDatabase
(Nothing, Just child) -> do
(root', cache'') <- loop child cache'
let branch' = True `setChild` Just root' $ branch
storeCold branch' cache'' _radixDatabase
(Just left, Just right) -> do
(root', cache'') <- loop left cache'
(root'', cache''') <- loop right cache''
let branch' = setChildren (Just root', Just root'') branch
storeCold branch' cache''' _radixDatabase
sourceMerkleizedRadixTree
:: MonadResource m
=> [Bool]
-> Int
-> BoundedChan RadixRoot
-> RadixTree
-> Source m ByteString
{-# SPECIALISE sourceMerkleizedRadixTree
:: [Bool]
-> Int
-> BoundedChan RadixRoot
-> RadixTree
-> Source (ResourceT IO) ByteString #-}
sourceMerkleizedRadixTree patten cacheSize chan
| cacheSize <= 0 = throw $ InvalidArgument "invalid LRU cache size"
| otherwise = \ tree -> do
cache <- liftIO $ newMVar $ LRU.empty cacheSize
(,) action _ <- flip allocate killThread $ forkIO $ forever $ do
root <- readChan chan
modifyMVar_ cache $ pure . LRU.insert root ()
loop cache tree []
release action
where
loop cache tree@RadixTree {..} roots = do
seen <- liftIO $ readMVar cache
let roots' = _radixCheckpoint:roots
if flip any roots' $ isJust . flip LRU.lookup seen
then pure ()
else do
let key = fromShort _radixCheckpoint
result <- get _radixDatabase defaultReadOptions key
case result of
Nothing -> pure ()
Just bytes -> do
let RadixBranch {..} = deserialise $ fromStrict bytes
let success = all id $ zipWith (==) patten $ toBits $ fromShort _radixCheckpoint
when success $ yield bytes
forM_ [_radixLeft, _radixRight] $ \ case
Nothing -> pure ()
Just root -> loop cache `flip` roots' $ setCheckpoint root tree
printRadixTree
:: MonadIO m
=> Bool
-> (RadixTree -> m (Maybe (RadixBranch, RadixCache)))
-> RadixTree
-> m ()
{-# SPECIALISE printRadixTree
:: Bool
-> (RadixTree -> ResourceT IO (Maybe (RadixBranch, RadixCache)))
-> RadixTree
-> ResourceT IO () #-}
printRadixTree flag load = \ tree@RadixTree {..} -> do
let tree' = tree `bool` setRoot _radixCheckpoint tree $ flag
loop tree' 0 where
loop tree@RadixTree {..} i = do
result <- load tree
case fst <$> result of
Nothing -> throw $ StateRootDoesNotExist _radixRoot
Just branch@RadixBranch {..} -> do
let indent = (++) $ concat $ replicate i "|"
liftIO $ putStrLn $ indent $ show branch
let j = i + 1
forM_ [_radixLeft, _radixRight] $ \ case
Nothing -> pure ()
Just root -> setRoot root tree `loop` j
printMerkleizedRadixTree
:: MonadIO m
=> RadixTree
-> m ()
{-# SPECIALISE printMerkleizedRadixTree
:: RadixTree
-> ResourceT IO () #-}
printMerkleizedRadixTree =
printRadixTree True $ \ RadixTree {..} ->
loadCold _radixRoot _radixCache _radixDatabase
printNonMerkleizedRadixTree
:: MonadIO m
=> RadixTree
-> m ()
{-# SPECIALISE printNonMerkleizedRadixTree
:: RadixTree
-> ResourceT IO () #-}
printNonMerkleizedRadixTree =
printRadixTree False $ \ RadixTree {..} ->
loadHot _radixRoot _radixBuffer _radixCache _radixDatabase