Skip to content

Commit

Permalink
Reorganize LedgerDB
Browse files Browse the repository at this point in the history
  • Loading branch information
jasagredo committed Dec 9, 2024
1 parent 8bdf17f commit 589b852
Show file tree
Hide file tree
Showing 47 changed files with 2,104 additions and 2,335 deletions.
4 changes: 2 additions & 2 deletions ouroboros-consensus-cardano/app/snapshot-converter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,8 +31,8 @@ import Ouroboros.Consensus.Ledger.Basics
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Ledger.Tables.Utils
import Ouroboros.Consensus.Node.ProtocolInfo
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Common
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Snapshots
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB as Disk
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB.Bridge as LMDB.Bridge
import Ouroboros.Consensus.Util.CBOR
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ import Ouroboros.Consensus.Shelley.HFEras ()
import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node ()
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
import Ouroboros.Consensus.Storage.LedgerDB.API
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.TypeFamilyWrappers

-- | Just to have the @x@ as the last type variable
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,7 +73,7 @@ import Ouroboros.Consensus.Protocol.TPraos
import Ouroboros.Consensus.Shelley.Eras
import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node
import Ouroboros.Consensus.Storage.LedgerDB.API
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.TypeFamilyWrappers
import Ouroboros.Consensus.Util (eitherToMaybe)
import Ouroboros.Consensus.Util.IOLike (IOLike)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,13 +30,11 @@ import Ouroboros.Consensus.Node.ProtocolInfo (ProtocolInfo (..))
import qualified Ouroboros.Consensus.Storage.ChainDB as ChainDB
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Args as ChainDB
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import qualified Ouroboros.Consensus.Storage.ImmutableDB.Impl.Stream as ImmutableDB
import qualified Ouroboros.Consensus.Storage.ImmutableDB.Stream as ImmutableDB
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB.Impl.Args as LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB.Impl.Init as LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1 as LedgerDB.V1
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.Args as LedgerDB.V1
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB as LMDB
import qualified Ouroboros.Consensus.Storage.LedgerDB.V1.Init as LedgerDB.V1
import qualified Ouroboros.Consensus.Storage.LedgerDB.V2.Args as LedgerDB.V2
import Ouroboros.Consensus.Util.Args
import Ouroboros.Consensus.Util.IOLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ import Ouroboros.Consensus.Storage.ChainDB.API as ChainDB
getReadOnlyForkerAtPoint)
import qualified Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment as InvalidBlockPunishment
(noPunishment)
import Ouroboros.Consensus.Storage.LedgerDB.API
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.Util.IOLike (atomically)
import Ouroboros.Network.AnchoredFragment as AF (Anchor (..),
AnchoredFragment, AnchoredSeq (..), headPoint)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ import Ouroboros.Consensus.Shelley.Node (ShelleyGenesis (..),
import qualified Ouroboros.Consensus.Storage.ChainDB as ChainDB (getTipPoint)
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl as ChainDB
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Args as ChainDB
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Args as LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.V1.Args as LedgerDB.V1
import Ouroboros.Consensus.Util.IOLike (atomically)
import Ouroboros.Network.Block
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -112,8 +112,8 @@ import Ouroboros.Consensus.Storage.ChainDB (ChainDB, ChainDbArgs,
TraceEvent)
import qualified Ouroboros.Consensus.Storage.ChainDB as ChainDB
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Args as ChainDB
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Args
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Snapshots
import Ouroboros.Consensus.Storage.LedgerDB (LedgerDbFlavorArgs)
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
import Ouroboros.Consensus.Util.Args
import Ouroboros.Consensus.Util.IOLike
import Ouroboros.Consensus.Util.Orphans ()
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,7 @@ import Ouroboros.Consensus.Storage.ChainDB.Impl.Args
import Ouroboros.Consensus.Storage.ChainDB.Impl.Types
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import Ouroboros.Consensus.Storage.LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Args as LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
import Ouroboros.Consensus.Util.Assert
import Ouroboros.Consensus.Util.Condense
Expand Down
20 changes: 8 additions & 12 deletions ouroboros-consensus/ouroboros-consensus.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,6 @@ library
Ouroboros.Consensus.Ledger.Tables.Basics
Ouroboros.Consensus.Ledger.Tables.Combinators
Ouroboros.Consensus.Ledger.Tables.Diff
Ouroboros.Consensus.Ledger.Tables.DiffSeq
Ouroboros.Consensus.Ledger.Tables.MapKind
Ouroboros.Consensus.Ledger.Tables.Utils
Ouroboros.Consensus.Mempool
Expand Down Expand Up @@ -229,36 +228,33 @@ library
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Iterator
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Parser
Ouroboros.Consensus.Storage.ImmutableDB.Impl.State
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Stream
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Types
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Util
Ouroboros.Consensus.Storage.ImmutableDB.Impl.Validation
Ouroboros.Consensus.Storage.ImmutableDB.Stream
Ouroboros.Consensus.Storage.LedgerDB
Ouroboros.Consensus.Storage.LedgerDB.API
Ouroboros.Consensus.Storage.LedgerDB.Impl.Args
Ouroboros.Consensus.Storage.LedgerDB.Impl.Common
Ouroboros.Consensus.Storage.LedgerDB.Impl.Init
Ouroboros.Consensus.Storage.LedgerDB.Impl.Snapshots
Ouroboros.Consensus.Storage.LedgerDB.Impl.Validate
Ouroboros.Consensus.Storage.LedgerDB.Forker
Ouroboros.Consensus.Storage.LedgerDB.Args
Ouroboros.Consensus.Storage.LedgerDB.TraceEvent
Ouroboros.Consensus.Storage.LedgerDB.Snapshots
Ouroboros.Consensus.Storage.LedgerDB.V1.Args
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.InMemory
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB.Bridge
Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.Impl.LMDB.Status
Ouroboros.Consensus.Storage.LedgerDB.V1.Common
Ouroboros.Consensus.Storage.LedgerDB.V1.DbChangelog
Ouroboros.Consensus.Storage.LedgerDB.V1.Flush
Ouroboros.Consensus.Storage.LedgerDB.V1.Forker
Ouroboros.Consensus.Storage.LedgerDB.V1.Init
Ouroboros.Consensus.Storage.LedgerDB.V1.DiffSeq
Ouroboros.Consensus.Storage.LedgerDB.V1
Ouroboros.Consensus.Storage.LedgerDB.V1.Lock
Ouroboros.Consensus.Storage.LedgerDB.V1.Snapshots
Ouroboros.Consensus.Storage.LedgerDB.V2.Args
Ouroboros.Consensus.Storage.LedgerDB.V2.Common
Ouroboros.Consensus.Storage.LedgerDB.V2.Forker
Ouroboros.Consensus.Storage.LedgerDB.V2.InMemory
Ouroboros.Consensus.Storage.LedgerDB.V2.Init
Ouroboros.Consensus.Storage.LedgerDB.V2
Ouroboros.Consensus.Storage.LedgerDB.V2.LedgerSeq
Ouroboros.Consensus.Storage.Serialisation
Ouroboros.Consensus.Storage.VolatileDB
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,6 @@ import Ouroboros.Consensus.Node.Serialisation
(SerialiseBlockQueryResult (..),
SerialiseNodeToClient (..), SerialiseResult (..))
import Ouroboros.Consensus.Storage.LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import Ouroboros.Consensus.Util (ShowProxy (..), SomeSecond (..))
import Ouroboros.Consensus.Util.DepPair
import Ouroboros.Consensus.Util.IOLike
Expand Down Expand Up @@ -221,7 +220,7 @@ answerQuery config forker query = case query of
case sing :: Sing footprint of
SQFNoTables ->
answerPureBlockQuery config blockQuery <$>
atomically (LedgerDB.roforkerGetLedgerState forker)
atomically (roforkerGetLedgerState forker)
SQFLookupTables ->
answerBlockQueryLookup config blockQuery forker
SQFTraverseTables ->
Expand All @@ -230,10 +229,10 @@ answerQuery config forker query = case query of
pure $ getSystemStart (topLevelConfigBlock (getExtLedgerCfg config))
GetChainBlockNo ->
headerStateBlockNo . headerState <$>
atomically (LedgerDB.roforkerGetLedgerState forker)
atomically (roforkerGetLedgerState forker)
GetChainPoint ->
headerStatePoint . headerState <$>
atomically (LedgerDB.roforkerGetLedgerState forker)
atomically (roforkerGetLedgerState forker)

{-------------------------------------------------------------------------------
Query instances
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,15 +35,12 @@ module Ouroboros.Consensus.Ledger.Tables.Diff (
-- * Filter
, filterWithKeyOnly
, foldMapDelta
, fromAntiDiff
, toAntiDiff
, traverseDeltaWithKey_
) where

import Control.Monad (void)
import Data.Bifunctor
import Data.Foldable (foldMap')
import qualified Data.Map.Diff.Strict.Internal as Anti
import qualified Data.Map.Merge.Strict as Merge
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
Expand Down Expand Up @@ -193,22 +190,6 @@ applyDiffForKeys m ks (Diff diffs) =
filterWithKeyOnly :: (k -> Bool) -> Diff k v -> Diff k v
filterWithKeyOnly f (Diff m) = Diff $ Map.filterWithKey (const . f) m

{-------------------------------------------------------------------------------
From-to anti-diffs
-------------------------------------------------------------------------------}

fromAntiDiff :: Anti.Diff k v -> Diff k v
fromAntiDiff (Anti.Diff d) = Diff (Map.map (f . Anti.last) d)
where
f (Anti.Insert v) = Insert v
f Anti.Delete{} = Delete

toAntiDiff :: Diff k v -> Anti.Diff k v
toAntiDiff (Diff d) = Anti.Diff (Map.map f d)
where
f (Insert v) = Anti.singletonInsert v
f Delete = Anti.singletonDelete

{-------------------------------------------------------------------------------
Traversals and folds
-------------------------------------------------------------------------------}
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ import GHC.Generics (Generic)
import NoThunks.Class
import Ouroboros.Consensus.Ledger.Tables.Basics
import Ouroboros.Consensus.Ledger.Tables.Diff (Diff (..))
import Ouroboros.Consensus.Ledger.Tables.DiffSeq
import Ouroboros.Consensus.Storage.LedgerDB.V1.DiffSeq

{-------------------------------------------------------------------------------
Classes
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Iterator as Iterator
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Query as Query
import Ouroboros.Consensus.Storage.ChainDB.Impl.Types
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import qualified Ouroboros.Consensus.Storage.ImmutableDB.Impl.Stream as ImmutableDB
import qualified Ouroboros.Consensus.Storage.ImmutableDB.Stream as ImmutableDB
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
import Ouroboros.Consensus.Util (newFuse, whenJust, withFuse)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -33,11 +33,9 @@ import Ouroboros.Consensus.Storage.ChainDB.API (GetLoEFragment,
import Ouroboros.Consensus.Storage.ChainDB.Impl.Types
(TraceEvent (..))
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import qualified Ouroboros.Consensus.Storage.LedgerDB.API as LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Args
(LedgerDbFlavorArgs)
import qualified Ouroboros.Consensus.Storage.LedgerDB.Impl.Args as LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Impl.Snapshots
import Ouroboros.Consensus.Storage.LedgerDB (LedgerDbFlavorArgs)
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import Ouroboros.Consensus.Storage.LedgerDB.Snapshots
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
import Ouroboros.Consensus.Util.Args
import Ouroboros.Consensus.Util.IOLike
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -73,8 +73,7 @@ import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.Query as Query
import Ouroboros.Consensus.Storage.ChainDB.Impl.Types
import Ouroboros.Consensus.Storage.ImmutableDB (ImmutableDB)
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import Ouroboros.Consensus.Storage.LedgerDB (AnnLedgerError (..),
Forker', LedgerDB', ValidateResult (..))
import Ouroboros.Consensus.Storage.LedgerDB
import qualified Ouroboros.Consensus.Storage.LedgerDB as LedgerDB
import Ouroboros.Consensus.Storage.VolatileDB (VolatileDB)
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
Expand Down Expand Up @@ -103,7 +102,7 @@ initialChainSelection ::
)
=> ImmutableDB m blk
-> VolatileDB m blk
-> LedgerDB' m blk
-> LedgerDB.LedgerDB' m blk
-> ResourceRegistry m
-> Tracer m (TraceInitChainSelEvent blk)
-> TopLevelConfig blk
Expand Down Expand Up @@ -146,7 +145,7 @@ initialChainSelection immutableDB volatileDB lgrDB rr tracer cfg varInvalid
chainSelection' curChainAndLedger chains' >>= \case
-- The returned forker will be closed in 'openDBInternal'.
Nothing -> pure curChainAndLedger
Just newChain -> LedgerDB.forkerClose curForker >> toChainAndLedger newChain
Just newChain -> forkerClose curForker >> toChainAndLedger newChain
where
bcfg :: BlockConfig blk
bcfg = configBlock cfg
Expand Down Expand Up @@ -216,7 +215,7 @@ initialChainSelection immutableDB volatileDB lgrDB rr tracer cfg varInvalid
-- ^ Candidates anchored at @i@
-> m (Maybe (ValidatedChainDiff (Header blk) (Forker' m blk)))
chainSelection' curChainAndLedger candidates =
atomically (LedgerDB.forkerCurrentPoint ledger) >>= \curpt ->
atomically (forkerCurrentPoint ledger) >>= \curpt ->
assert (all ((curpt ==) . castPoint . AF.anchorPoint) candidates) $
assert (all (preferAnchoredCandidate bcfg curChain) candidates) $ do
cse <- chainSelEnv
Expand Down Expand Up @@ -905,14 +904,14 @@ chainSelectionForBlock cdb@CDB{..} blockCache hdr punish = electric $ withRegist
(curChain, newChain, events, prevTentativeHeader, newLedger) <- atomically $ do
curChain <- readTVar cdbChain -- Not Query.getCurrentChain!
curLedger <- tipLegerDB
newLedger <- LedgerDB.forkerGetLedgerState newForker
newLedger <- forkerGetLedgerState newForker
case Diff.apply curChain chainDiff of
-- Impossible, as described in the docstring
Nothing ->
error "chainDiff doesn't fit onto current chain"
Just newChain -> do
writeTVar cdbChain newChain
LedgerDB.forkerCommit newForker
forkerCommit newForker
-- Inspect the new ledger for potential problems
let events :: [LedgerEvent blk]
events = inspectLedger
Expand Down Expand Up @@ -949,7 +948,7 @@ chainSelectionForBlock cdb@CDB{..} blockCache hdr punish = electric $ withRegist
whenJust (strictMaybeToMaybe prevTentativeHeader) $ traceWith $
PipeliningEvent . OutdatedTentativeHeader >$< addBlockTracer

LedgerDB.forkerClose newForker
forkerClose newForker

return $ castPoint $ AF.headPoint newChain
where
Expand Down Expand Up @@ -1004,7 +1003,7 @@ getKnownHeaderThroughCache volatileDB hash = gets (Map.lookup hash) >>= \case

-- | Environment used by 'chainSelection' and related functions.
data ChainSelEnv m blk = ChainSelEnv
{ lgrDB :: LedgerDB' m blk
{ lgrDB :: LedgerDB.LedgerDB' m blk
, validationTracer :: Tracer m (TraceValidationEvent blk)
, pipeliningTracer :: Tracer m (TracePipeliningEvent blk)
, bcfg :: BlockConfig blk
Expand Down Expand Up @@ -1243,15 +1242,15 @@ ledgerValidateCandidate ::
-> ChainDiff (Header blk)
-> m (ValidatedChainDiff (Header blk) (Forker' m blk))
ledgerValidateCandidate chainSelEnv rr chainDiff@(ChainDiff rollback suffix) =
LedgerDB.validate lgrDB rr traceUpdate blockCache rollback newBlocks >>= \case
LedgerDB.validateFork lgrDB rr traceUpdate blockCache rollback newBlocks >>= \case
ValidateExceededRollBack {} ->
-- Impossible: we asked the LedgerDB to roll back past the immutable
-- tip, which is impossible, since the candidates we construct must
-- connect to the immutable tip.
error "found candidate requiring rolling back past the immutable tip"

ValidateLedgerError (AnnLedgerError ledger' pt e) -> do
lastValid <- atomically $ LedgerDB.forkerCurrentPoint ledger'
lastValid <- atomically $ forkerCurrentPoint ledger'
let chainDiff' = Diff.truncate (castPoint lastValid) chainDiff
traceWith validationTracer (InvalidBlock e pt)
addInvalidBlock e pt
Expand Down Expand Up @@ -1388,7 +1387,7 @@ futureCheckCandidate chainSelEnv validatedChainDiff = do
getValidatedSuffix :: m (ValidatedFragment (Header blk) (LedgerState blk EmptyMK))
getValidatedSuffix =
ValidatedDiff.toValidatedFragmentM validatedChainDiff >>=
mapM (fmap ledgerState . atomically . LedgerDB.forkerGetLedgerState)
mapM (fmap ledgerState . atomically . forkerGetLedgerState)


-- | Validate a candidate chain using 'ledgerValidateCandidate' and
Expand Down Expand Up @@ -1434,7 +1433,7 @@ validateCandidate chainSelEnv rr chainDiff =
-- leftover forker that we have to close so that its resources are correctly
-- released.
cleanup :: ValidatedChainDiff b (Forker' m blk) -> m ()
cleanup = LedgerDB.forkerClose . getLedger
cleanup = forkerClose . getLedger

{-------------------------------------------------------------------------------
'ChainAndLedger'
Expand Down
Loading

0 comments on commit 589b852

Please sign in to comment.