{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE RecordWildCards #-} {-# OPTIONS -Wall #-} {-# OPTIONS -Werror=incomplete-patterns #-} -- | -- Module : Network.DFINITY.RadixTree -- Copyright : 2018 DFINITY Stiftung -- License : GPL-3 -- Maintainer : Enzo Haussecker -- Stability : Stable -- -- A generic data integrity layer. module Network.DFINITY.RadixTree ( -- ** Class RadixDatabase(..) -- ** Types , RadixRoot , RadixTree , RadixError(..) -- ** Create , createRadixTree , subtreeRadixTree -- ** Insert , insertRadixTree -- ** Delete , deleteRadixTree -- ** Merkleize , merkleizeRadixTree -- ** Query , lookupMerkleizedRadixTree , lookupNonMerkleizedRadixTree -- ** Test , isEmptyRadixTree , isValidRadixRoot -- ** Stream , sourceMerkleizedRadixTree , sinkMerkleizedRadixTree -- ** Debug , printMerkleizedRadixTree , printNonMerkleizedRadixTree ) where import Codec.Serialise (deserialise, deserialiseOrFail) import Control.Concurrent (forkIO, killThread) import Control.Concurrent.BoundedChan (BoundedChan, readChan, tryWriteChan) import Control.Concurrent.MVar (modifyMVar_, newMVar, readMVar) import Control.Exception (throw) import Control.Monad (foldM, forM_, forever, void, when) import Control.Monad.IO.Class (MonadIO(..)) import Control.Monad.Trans.Resource (MonadResource, ResourceT, allocate, release) import Crypto.Hash.SHA256 (hash) import Data.BloomFilter as Bloom (elem, insert, insertList) import Data.Bool (bool) import Data.ByteString.Char8 as Byte (ByteString, take) import Data.ByteString.Lazy (fromStrict) import Data.ByteString.Short (fromShort, toShort) import Data.Conduit (ConduitM, await, yield) import Data.Default.Class (def) import Data.List as List (delete, foldl', null) import Data.List.NonEmpty (NonEmpty(..), fromList) import Data.LruCache as LRU (empty, insert, lookup) import Data.Map.Strict as Map ((!), delete, empty, insert, keys, lookup, member, null, singleton) import Data.Maybe (fromJust, isJust, isNothing, listToMaybe) import Data.Tuple (swap) import Database.LevelDB (DB, Options) 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 -- | -- Create a radix tree. createRadixTree :: 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) {-# SPECIALISE createRadixTree :: Int -> Int -> Maybe RadixRoot -> (FilePath, Options) -> ResourceT IO (RadixTree DB) #-} createRadixTree bloomSize cacheSize checkpoint config | bloomSize <= 0 = throw $ InvalidArgument "invalid Bloom filter size" | cacheSize <= 0 = throw $ InvalidArgument "invalid LRU cache size" | otherwise = do database <- create config (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 -- | -- Create a radix tree from a radix tree. subtreeRadixTree :: RadixDatabase config m database => RadixRoot -- ^ State root. -> RadixTree database -- ^ Radix tree. -> m (RadixTree database) {-# SPECIALISE subtreeRadixTree :: RadixRoot -> RadixTree DB -> ResourceT IO (RadixTree DB) #-} 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 -- | -- Check if a radix tree is empty. isEmptyRadixTree :: RadixTree database -- ^ Radix tree. -> Bool {-# INLINABLE isEmptyRadixTree #-} isEmptyRadixTree = (==) defaultRoot . _radixRoot -- | -- Check if a state root is valid. isValidRadixRoot :: RadixDatabase config m database => RadixRoot -- ^ State root. -> RadixTree database -- ^ Radix tree. -> m Bool {-# SPECIALISE isValidRadixRoot :: RadixRoot -> RadixTree DB -> ResourceT IO Bool #-} isValidRadixRoot root RadixTree {..} = isJust <$> load _radixDatabase key where key = fromShort root -- | -- Search for a value in a radix tree. searchRadixTree :: RadixDatabase config m database => Bool -- ^ Overwrite state root? -> (RadixTree database -> m (Maybe (RadixBranch, RadixCache))) -- ^ Loading strategy. -> ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Either RadixError RadixSearchResult) {-# SPECIALISE searchRadixTree :: Bool -> (RadixTree DB -> ResourceT IO (Maybe (RadixBranch, RadixCache))) -> ByteString -> RadixTree DB -> ResourceT IO (Either RadixError RadixSearchResult) #-} searchRadixTree flag strategy = \ 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 -- Load the root branch. result <- strategy tree case result of Nothing -> pure $ Left $ StateRootDoesNotExist _radixRoot Just (branch@RadixBranch {..}, cache') -> do -- Calculate the prefix and overflow. let bits = maybe id (:) implicit $ maybe [] toBits _radixPrefix let prefix = matchBits bits key let n = length prefix let overflow = drop n bits -- Update the accumulators. let roots' = _radixRoot:roots let branches' = branch:branches let prefixes' = prefix:prefixes let key' = drop n key -- Check the termination criteria. let residue = not $ List.null overflow let bit = head key' let child = bool _radixLeft _radixRight bit if List.null key' || residue || isNothing child then pure $ Right (fromList roots', fromList branches', fromList prefixes', overflow, key', cache') else do -- Recurse. let root' = fromJust child let tree' = setCache cache' $ setRoot root' tree let implicit' = Just bit loop implicit' branches' roots' prefixes' key' tree' -- | -- Search for a value in a Merkleized radix tree. searchMerkleizedRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Either RadixError RadixSearchResult) {-# SPECIALISE searchMerkleizedRadixTree :: ByteString -> RadixTree DB -> ResourceT IO (Either RadixError RadixSearchResult) #-} searchMerkleizedRadixTree = searchRadixTree True $ \ RadixTree {..} -> loadCold _radixRoot _radixCache _radixDatabase -- | -- Search for a value in a non-Merkleized radix tree. searchNonMerkleizedRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Either RadixError RadixSearchResult) {-# SPECIALISE searchNonMerkleizedRadixTree :: ByteString -> RadixTree DB -> ResourceT IO (Either RadixError RadixSearchResult) #-} searchNonMerkleizedRadixTree = searchRadixTree False $ \ RadixTree {..} -> loadHot _radixRoot _radixBuffer _radixCache _radixDatabase -- | -- Insert a key and value into a radix tree. insertRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> m (RadixTree database) {-# SPECIALISE insertRadixTree :: ByteString -> ByteString -> RadixTree DB -> ResourceT IO (RadixTree DB) #-} 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 -- TODO (enzo): Documentation. initializeRadixTree :: ByteString -- ^ Key. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. insertRadixTreeAt :: RadixSearchResult -- ^ Search result. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. insertRadixTreeAfter :: RadixSearchResult -- ^ Search result. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. insertRadixTreeBefore :: RadixSearchResult -- ^ Search result. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. insertRadixTreeBetween :: RadixSearchResult -- ^ Search result. -> ByteString -- ^ Value. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- | -- Delete a value from a radix tree. deleteRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (RadixTree database) {-# SPECIALISE deleteRadixTree :: ByteString -> RadixTree DB -> ResourceT IO (RadixTree DB) #-} 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 -- No children and no parent. RadixBranch _ Nothing Nothing _:|[] -> pure $ deleteRadixTreeNoChildrenNoParent result tree -- No children and parent with leaf. RadixBranch _ Nothing Nothing _:|parent:_ | isJust $ getLeaf parent -> pure $ deleteRadixTreeNoChildrenParentWithLeaf result tree -- No children and parent without leaf. 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 -- One left child. 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 -- One right child. 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 -- Two children. _ -> pure $ deleteRadixTreeTwoChildren result tree Right _ -> pure tree -- TODO (enzo): Documentation. deleteRadixTreeNoChildrenNoParent :: RadixSearchResult -- ^ Search result. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. deleteRadixTreeNoChildrenParentWithLeaf :: RadixSearchResult -- ^ Search result. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 deleteRadixTreeNoChildrenParentWithLeaf _ _ = throw $ InvalidArgument "unknown parent" -- TODO (enzo): Documentation. deleteRadixTreeNoChildrenParentWithoutLeaf :: RadixSearchResult -- ^ Search result. -> RadixBranch -- ^ Branch. -> RadixCache -- ^ Cache. -> Bool -- ^ Lineage. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 deleteRadixTreeNoChildrenParentWithoutLeaf _ _ _ _ _ = throw $ InvalidArgument "unknown parent" -- TODO (enzo): Documentation. deleteRadixTreeOneChild :: RadixSearchResult -- ^ Search result. -> RadixBranch -- ^ Branch. -> RadixCache -- ^ Cache. -> Bool -- ^ Lineage. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- TODO (enzo): Documentation. deleteRadixTreeTwoChildren :: RadixSearchResult -- ^ Search result. -> RadixTree database -- ^ Radix tree. -> RadixTree database {-# INLINABLE 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 -- | -- Lookup a value in a radix tree. lookupRadixTree :: RadixDatabase config m database => (ByteString -> RadixTree database -> m (Either RadixError RadixSearchResult)) -- ^ Search algorithm. -> ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Maybe (ByteString, RadixTree database)) {-# SPECIALISE lookupRadixTree :: (ByteString -> RadixTree DB -> ResourceT IO (Either RadixError RadixSearchResult)) -> ByteString -> RadixTree DB -> ResourceT IO (Maybe (ByteString, RadixTree DB)) #-} lookupRadixTree search key tree = do found <- search key tree case found of Left err -> throw err Right (_, RadixBranch {..}:|_, _, prefixOverflow, keyOverflow, cache') -> if not $ List.null prefixOverflow && List.null keyOverflow then pure Nothing else pure $ do value <- _radixLeaf let tree' = setCache cache' tree pure (value, tree') -- | -- Lookup a value in a Merkleized radix tree. lookupMerkleizedRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Maybe (ByteString, RadixTree database)) {-# SPECIALISE lookupMerkleizedRadixTree :: ByteString -> RadixTree DB -> ResourceT IO (Maybe (ByteString, RadixTree DB)) #-} lookupMerkleizedRadixTree = lookupRadixTree searchMerkleizedRadixTree -- | -- Lookup a value in a non-Merkleized radix tree. lookupNonMerkleizedRadixTree :: RadixDatabase config m database => ByteString -- ^ Key. -> RadixTree database -- ^ Radix tree. -> m (Maybe (ByteString, RadixTree database)) {-# SPECIALISE lookupNonMerkleizedRadixTree :: ByteString -> RadixTree DB -> ResourceT IO (Maybe (ByteString, RadixTree DB)) #-} lookupNonMerkleizedRadixTree = lookupRadixTree searchNonMerkleizedRadixTree -- | -- Mask a branch in a Merkleized radix tree. merkleSpoof :: RadixRoot -- ^ State root. -> Maybe (RadixRoot, RadixBranch, Bool) -- ^ Parent. -> RadixBuffer -- ^ Buffer. -> RadixBuffer {-# INLINABLE merkleSpoof #-} merkleSpoof mask = \ case Nothing -> id Just (root, branch, test) -> storeHot root $ test `setChild` Just mask $ branch -- | -- Merkleize a radix tree. This will flush the buffer to disk. merkleizeRadixTree :: RadixDatabase config m database => RadixTree database-- ^ Radix tree. -> m (RadixRoot, RadixTree database) {-# SPECIALISE merkleizeRadixTree :: RadixTree DB -> ResourceT IO (RadixRoot, RadixTree DB) #-} 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 -- Load the root branch. result <- loadHot root _radixBuffer cache _radixDatabase case result of Nothing -> throw $ StateRootDoesNotExist root Just (branch@RadixBranch {..}, cache') -> case (_radixLeft, _radixRight) of -- No children. (Nothing, Nothing) -> storeCold branch cache' _radixDatabase -- One left child. (Just child, Nothing) -> do (root', cache'') <- loop child cache' let branch' = False `setChild` Just root' $ branch storeCold branch' cache'' _radixDatabase -- One right child. (Nothing, Just child) -> do (root', cache'') <- loop child cache' let branch' = True `setChild` Just root' $ branch storeCold branch' cache'' _radixDatabase -- Two children. (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 -- | -- Create a conduit from a Merkleized radix tree. sourceMerkleizedRadixTree :: 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 () {-# SPECIALISE sourceMerkleizedRadixTree :: [Bool] -> Int -> BoundedChan RadixRoot -> RadixTree DB -> ConduitM () ByteString (ResourceT IO) () #-} sourceMerkleizedRadixTree mask 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 <- load _radixDatabase key case result of Nothing -> pure () Just bytes -> do let RadixBranch {..} = deserialise $ fromStrict bytes let success = all id $ zipWith (==) mask $ toBits $ fromShort _radixCheckpoint when success $ yield bytes forM_ [_radixLeft, _radixRight] $ \ case Nothing -> pure () Just root -> loop cache `flip` roots' $ setCheckpoint root tree -- | -- Create a Merkleized radix tree from a conduit. sinkMerkleizedRadixTree :: 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)) {-# SPECIALISE sinkMerkleizedRadixTree :: RadixRoot -> BoundedChan RadixRoot -> RadixTree DB -> ConduitM ByteString () (ResourceT IO) (Either [RadixRoot] (RadixTree DB)) #-} sinkMerkleizedRadixTree checkpoint chan tree@RadixTree {..} = loop1 Map.empty $ singleton checkpoint Nothing where loop1 = \ buffer want -> if Map.null want then pure $ Right $ setCheckpoint checkpoint $ setRoot checkpoint tree else await >>= \ case Nothing -> pure $ Left $ keys want Just bytes -> case deserialiseOrFail $ fromStrict bytes of Right RadixBranch {..} -> do let key = Byte.take 20 $ hash bytes let root = toShort key let wanted = member root want exists <- if wanted then pure False else isJust <$> load _radixDatabase key if exists then loop1 buffer $ Map.delete root want else do children <- foldM step [] $ maybe id (:) _radixLeft $ maybe id (:) _radixRight [] let buffer' = Map.insert root (key, bytes, children) buffer if not wanted then loop1 buffer' want else loop3 buffer' `uncurry` loop2 buffer' (want, []) root _ -> loop1 buffer want where step accum root = do valid <- isValidRadixRoot root tree if valid then pure accum else pure $ root:accum loop2 buffer accum@(want, candidates) root = case Map.lookup root buffer of Nothing -> accum Just (key, bytes, []) -> (want, (root, key, bytes):candidates) Just (_, _, children) -> let want' = foldr step want children in foldl' (loop2 buffer) (want', candidates) children where step = flip Map.insert $ Just root loop3 buffer want = \ case [] -> loop1 buffer want (root, key, bytes):candidates -> do store _radixDatabase key bytes let buffer' = Map.delete root buffer case want ! root of Nothing -> do let want' = Map.delete root want loop1 buffer' want' Just root' -> do let want' = Map.delete root want let (key', bytes', siblings') = buffer ! root' let children' = List.delete root siblings' if List.null children' then loop3 buffer' want' $ (root', key', bytes'):candidates else do let buffer'' = Map.insert root' (key', bytes', children') buffer' liftIO $ void $ tryWriteChan chan root loop3 buffer'' want' candidates -- | -- Print a radix tree. printRadixTree :: MonadIO m => RadixDatabase config m database => Bool -- ^ Overwrite state root? -> (RadixTree database -> m (Maybe (RadixBranch, RadixCache))) -- ^ Loading strategy. -> RadixTree database -- ^ Radix tree. -> m () {-# SPECIALISE printRadixTree :: Bool -> (RadixTree DB -> ResourceT IO (Maybe (RadixBranch, RadixCache))) -> RadixTree DB -> ResourceT IO () #-} printRadixTree flag strategy = \ tree@RadixTree {..} -> do let tree' = tree `bool` setRoot _radixCheckpoint tree $ flag loop tree' 0 where loop tree@RadixTree {..} i = do result <- strategy 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 -- | -- Print a Merkleized radix tree. printMerkleizedRadixTree :: MonadIO m => RadixDatabase config m database => RadixTree database -- ^ Radix tree. -> m () {-# SPECIALISE printMerkleizedRadixTree :: RadixTree DB -> ResourceT IO () #-} printMerkleizedRadixTree = printRadixTree True $ \ RadixTree {..} -> loadCold _radixRoot _radixCache _radixDatabase -- | -- Print a non-Merkleized radix tree. printNonMerkleizedRadixTree :: MonadIO m => RadixDatabase config m database => RadixTree database -- ^ Radix tree. -> m () {-# SPECIALISE printNonMerkleizedRadixTree :: RadixTree DB -> ResourceT IO () #-} printNonMerkleizedRadixTree = printRadixTree False $ \ RadixTree {..} -> loadHot _radixRoot _radixBuffer _radixCache _radixDatabase