Skip to content

Commit

Permalink
Reduce ChainDB memory usage
Browse files Browse the repository at this point in the history
After some heap profiling, these bangs provided the most bang for the
buck (sorry for the pun).

For example, the memory usage of adding the first 30,000 blocks from disk (so
as fast as we can read them) to the ChainDB reduced from +240 MiB (and
growing) to 80 MiB. Note that these measurements were performed with block
validation disabled.
  • Loading branch information
mrBliss committed Aug 14, 2019
1 parent e50822f commit 075ac68
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 7 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ import Ouroboros.Consensus.Util (repeatedlyM)
--
-- This is the combination of the ouroboros state and the ledger state proper.
data ExtLedgerState blk = ExtLedgerState {
ledgerState :: LedgerState blk
, ouroborosChainState :: ChainState (BlockProtocol blk)
ledgerState :: !(LedgerState blk)
, ouroborosChainState :: !(ChainState (BlockProtocol blk))
}

data ExtValidationError blk =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -330,7 +330,7 @@ getCurrentState LgrDB{..} = LedgerDB.ledgerDbCurrent <$> readTVar varDB
-- 'LedgerDB'.
setCurrent :: MonadSTM m
=> LgrDB m blk -> LedgerDB blk -> STM m ()
setCurrent LgrDB{..} = writeTVar varDB
setCurrent LgrDB{..} = writeTVar $! varDB

currentPoint :: UpdateLedger blk
=> LedgerDB blk -> Point blk
Expand Down
2 changes: 1 addition & 1 deletion ouroboros-consensus/src/Ouroboros/Storage/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,7 +53,7 @@ type SlotOffset = Word64
-------------------------------------------------------------------------------}

-- | Tip of the chain
data Tip r = Tip r | TipGen
data Tip r = Tip !r | TipGen
deriving (Show, Eq, Generic)

instance Condense r => Condense (Tip r) where
Expand Down
6 changes: 3 additions & 3 deletions ouroboros-network/src/Ouroboros/Network/Point.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}

Expand All @@ -11,9 +11,9 @@ module Ouroboros.Network.Point
, block
) where

import GHC.Generics (Generic)
import GHC.Generics (Generic)

data WithOrigin t = Origin | At t
data WithOrigin t = Origin | At !t
deriving (Eq, Ord, Show, Generic, Functor, Foldable, Traversable)

data Block slot hash = Block
Expand Down

0 comments on commit 075ac68

Please sign in to comment.