{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
module Ouroboros.Consensus.Storage.ChainDB.Impl.Types (
ChainDbEnv (..)
, ChainDbHandle (..)
, ChainDbState (..)
, SerialiseDiskConstraints
, getEnv
, getEnv1
, getEnv2
, getEnvSTM
, getEnvSTM1
, Internal (..)
, IteratorKey (..)
, FollowerHandle (..)
, FollowerKey (..)
, FollowerRollState (..)
, FollowerState (..)
, followerRollStatePoint
, InvalidBlockInfo (..)
, InvalidBlocks
, FutureBlocks
, BlockToAdd (..)
, BlocksToAdd
, addBlockToAdd
, getBlockToAdd
, newBlocksToAdd
, NewTipInfo (..)
, TraceAddBlockEvent (..)
, TraceCopyToImmutableDBEvent (..)
, TraceEvent (..)
, TraceFollowerEvent (..)
, TraceGCEvent (..)
, TraceInitChainSelEvent (..)
, TraceIteratorEvent (..)
, TraceOpenEvent (..)
, TracePipeliningEvent (..)
, TraceValidationEvent (..)
) where
import Control.Tracer
import Data.Map.Strict (Map)
import Data.Maybe.Strict (StrictMaybe (..))
import Data.Typeable
import Data.Void (Void)
import Data.Word (Word64)
import GHC.Generics (Generic)
import NoThunks.Class (OnlyCheckWhnfNamed (..))
import Control.Monad.Class.MonadSTM.Strict (newEmptyTMVarIO)
import Ouroboros.Network.AnchoredFragment (AnchoredFragment)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Config
import Ouroboros.Consensus.Fragment.Diff (ChainDiff)
import Ouroboros.Consensus.Fragment.InFuture (CheckInFuture)
import Ouroboros.Consensus.Ledger.Extended (ExtValidationError)
import Ouroboros.Consensus.Ledger.Inspect
import Ouroboros.Consensus.Ledger.SupportsProtocol
import Ouroboros.Consensus.Storage.LedgerDB.Types
(UpdateLedgerDbTraceEvent)
import Ouroboros.Consensus.Util.CallStack
import Ouroboros.Consensus.Util.IOLike
import Ouroboros.Consensus.Util.ResourceRegistry
import Ouroboros.Consensus.Util.STM (WithFingerprint)
import Ouroboros.Consensus.Storage.ChainDB.API (AddBlockPromise (..),
ChainDbError (..), ChainType, InvalidBlockReason,
StreamFrom, StreamTo, UnknownRange)
import Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment
(InvalidBlockPunishment)
import Ouroboros.Consensus.Storage.Serialisation
import Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB (LedgerDB',
LgrDB, LgrDbSerialiseConstraints)
import qualified Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB as LgrDB
import Ouroboros.Consensus.Storage.ImmutableDB (ImmutableDB,
ImmutableDbSerialiseConstraints)
import qualified Ouroboros.Consensus.Storage.ImmutableDB as ImmutableDB
import Ouroboros.Consensus.Storage.VolatileDB (VolatileDB,
VolatileDbSerialiseConstraints)
import qualified Ouroboros.Consensus.Storage.VolatileDB as VolatileDB
import Ouroboros.Consensus.Util.Enclose (Enclosing, Enclosing' (..))
import Ouroboros.Consensus.Util.TentativeState (TentativeState (..))
class ( ImmutableDbSerialiseConstraints blk
, LgrDbSerialiseConstraints blk
, VolatileDbSerialiseConstraints blk
, EncodeDiskDep (NestedCtxt Header) blk
) => SerialiseDiskConstraints blk
newtype ChainDbHandle m blk = CDBHandle (StrictTVar m (ChainDbState m blk))
getEnv :: forall m blk r. (IOLike m, HasCallStack, HasHeader blk)
=> ChainDbHandle m blk
-> (ChainDbEnv m blk -> m r)
-> m r
getEnv :: ChainDbHandle m blk -> (ChainDbEnv m blk -> m r) -> m r
getEnv (CDBHandle StrictTVar m (ChainDbState m blk)
varState) ChainDbEnv m blk -> m r
f = STM m (ChainDbState m blk) -> m (ChainDbState m blk)
forall (m :: * -> *) a.
(MonadSTM m, HasCallStack) =>
STM m a -> m a
atomically (StrictTVar m (ChainDbState m blk) -> STM m (ChainDbState m blk)
forall (m :: * -> *) a. MonadSTM m => StrictTVar m a -> STM m a
readTVar StrictTVar m (ChainDbState m blk)
varState) m (ChainDbState m blk) -> (ChainDbState m blk -> m r) -> m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
ChainDbOpen ChainDbEnv m blk
env -> ChainDbEnv m blk -> m r
f ChainDbEnv m blk
env
ChainDbState m blk
ChainDbClosed -> ChainDbError blk -> m r
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (ChainDbError blk -> m r) -> ChainDbError blk -> m r
forall a b. (a -> b) -> a -> b
$ PrettyCallStack -> ChainDbError blk
forall blk. PrettyCallStack -> ChainDbError blk
ClosedDBError @blk PrettyCallStack
HasCallStack => PrettyCallStack
prettyCallStack
getEnv1 :: (IOLike m, HasCallStack, HasHeader blk)
=> ChainDbHandle m blk
-> (ChainDbEnv m blk -> a -> m r)
-> a -> m r
getEnv1 :: ChainDbHandle m blk -> (ChainDbEnv m blk -> a -> m r) -> a -> m r
getEnv1 ChainDbHandle m blk
h ChainDbEnv m blk -> a -> m r
f a
a = ChainDbHandle m blk -> (ChainDbEnv m blk -> m r) -> m r
forall (m :: * -> *) blk r.
(IOLike m, HasCallStack, HasHeader blk) =>
ChainDbHandle m blk -> (ChainDbEnv m blk -> m r) -> m r
getEnv ChainDbHandle m blk
h (\ChainDbEnv m blk
env -> ChainDbEnv m blk -> a -> m r
f ChainDbEnv m blk
env a
a)
getEnv2 :: (IOLike m, HasCallStack, HasHeader blk)
=> ChainDbHandle m blk
-> (ChainDbEnv m blk -> a -> b -> m r)
-> a -> b -> m r
getEnv2 :: ChainDbHandle m blk
-> (ChainDbEnv m blk -> a -> b -> m r) -> a -> b -> m r
getEnv2 ChainDbHandle m blk
h ChainDbEnv m blk -> a -> b -> m r
f a
a b
b = ChainDbHandle m blk -> (ChainDbEnv m blk -> m r) -> m r
forall (m :: * -> *) blk r.
(IOLike m, HasCallStack, HasHeader blk) =>
ChainDbHandle m blk -> (ChainDbEnv m blk -> m r) -> m r
getEnv ChainDbHandle m blk
h (\ChainDbEnv m blk
env -> ChainDbEnv m blk -> a -> b -> m r
f ChainDbEnv m blk
env a
a b
b)
getEnvSTM :: forall m blk r. (IOLike m, HasCallStack, HasHeader blk)
=> ChainDbHandle m blk
-> (ChainDbEnv m blk -> STM m r)
-> STM m r
getEnvSTM :: ChainDbHandle m blk -> (ChainDbEnv m blk -> STM m r) -> STM m r
getEnvSTM (CDBHandle StrictTVar m (ChainDbState m blk)
varState) ChainDbEnv m blk -> STM m r
f = StrictTVar m (ChainDbState m blk) -> STM m (ChainDbState m blk)
forall (m :: * -> *) a. MonadSTM m => StrictTVar m a -> STM m a
readTVar StrictTVar m (ChainDbState m blk)
varState STM m (ChainDbState m blk)
-> (ChainDbState m blk -> STM m r) -> STM m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
ChainDbOpen ChainDbEnv m blk
env -> ChainDbEnv m blk -> STM m r
f ChainDbEnv m blk
env
ChainDbState m blk
ChainDbClosed -> ChainDbError blk -> STM m r
forall (m :: * -> *) e a.
(MonadSTM m, MonadThrow (STM m), Exception e) =>
e -> STM m a
throwSTM (ChainDbError blk -> STM m r) -> ChainDbError blk -> STM m r
forall a b. (a -> b) -> a -> b
$ PrettyCallStack -> ChainDbError blk
forall blk. PrettyCallStack -> ChainDbError blk
ClosedDBError @blk PrettyCallStack
HasCallStack => PrettyCallStack
prettyCallStack
getEnvSTM1 ::
forall m blk a r. (IOLike m, HasCallStack, HasHeader blk)
=> ChainDbHandle m blk
-> (ChainDbEnv m blk -> a -> STM m r)
-> a -> STM m r
getEnvSTM1 :: ChainDbHandle m blk
-> (ChainDbEnv m blk -> a -> STM m r) -> a -> STM m r
getEnvSTM1 (CDBHandle StrictTVar m (ChainDbState m blk)
varState) ChainDbEnv m blk -> a -> STM m r
f a
a = StrictTVar m (ChainDbState m blk) -> STM m (ChainDbState m blk)
forall (m :: * -> *) a. MonadSTM m => StrictTVar m a -> STM m a
readTVar StrictTVar m (ChainDbState m blk)
varState STM m (ChainDbState m blk)
-> (ChainDbState m blk -> STM m r) -> STM m r
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
ChainDbOpen ChainDbEnv m blk
env -> ChainDbEnv m blk -> a -> STM m r
f ChainDbEnv m blk
env a
a
ChainDbState m blk
ChainDbClosed -> ChainDbError blk -> STM m r
forall (m :: * -> *) e a.
(MonadSTM m, MonadThrow (STM m), Exception e) =>
e -> STM m a
throwSTM (ChainDbError blk -> STM m r) -> ChainDbError blk -> STM m r
forall a b. (a -> b) -> a -> b
$ PrettyCallStack -> ChainDbError blk
forall blk. PrettyCallStack -> ChainDbError blk
ClosedDBError @blk PrettyCallStack
HasCallStack => PrettyCallStack
prettyCallStack
data ChainDbState m blk
= ChainDbOpen !(ChainDbEnv m blk)
| ChainDbClosed
deriving ((forall x. ChainDbState m blk -> Rep (ChainDbState m blk) x)
-> (forall x. Rep (ChainDbState m blk) x -> ChainDbState m blk)
-> Generic (ChainDbState m blk)
forall x. Rep (ChainDbState m blk) x -> ChainDbState m blk
forall x. ChainDbState m blk -> Rep (ChainDbState m blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: * -> *) blk x.
Rep (ChainDbState m blk) x -> ChainDbState m blk
forall (m :: * -> *) blk x.
ChainDbState m blk -> Rep (ChainDbState m blk) x
$cto :: forall (m :: * -> *) blk x.
Rep (ChainDbState m blk) x -> ChainDbState m blk
$cfrom :: forall (m :: * -> *) blk x.
ChainDbState m blk -> Rep (ChainDbState m blk) x
Generic, Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
Proxy (ChainDbState m blk) -> String
(Context -> ChainDbState m blk -> IO (Maybe ThunkInfo))
-> (Context -> ChainDbState m blk -> IO (Maybe ThunkInfo))
-> (Proxy (ChainDbState m blk) -> String)
-> NoThunks (ChainDbState m blk)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk.
(IOLike m, LedgerSupportsProtocol blk) =>
Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk.
(IOLike m, LedgerSupportsProtocol blk) =>
Proxy (ChainDbState m blk) -> String
showTypeOf :: Proxy (ChainDbState m blk) -> String
$cshowTypeOf :: forall (m :: * -> *) blk.
(IOLike m, LedgerSupportsProtocol blk) =>
Proxy (ChainDbState m blk) -> String
wNoThunks :: Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk.
(IOLike m, LedgerSupportsProtocol blk) =>
Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (m :: * -> *) blk.
(IOLike m, LedgerSupportsProtocol blk) =>
Context -> ChainDbState m blk -> IO (Maybe ThunkInfo)
NoThunks)
data ChainDbEnv m blk = CDB
{ ChainDbEnv m blk -> ImmutableDB m blk
cdbImmutableDB :: !(ImmutableDB m blk)
, ChainDbEnv m blk -> VolatileDB m blk
cdbVolatileDB :: !(VolatileDB m blk)
, ChainDbEnv m blk -> LgrDB m blk
cdbLgrDB :: !(LgrDB m blk)
, ChainDbEnv m blk -> StrictTVar m (AnchoredFragment (Header blk))
cdbChain :: !(StrictTVar m (AnchoredFragment (Header blk)))
, ChainDbEnv m blk -> StrictTVar m (TentativeState blk)
cdbTentativeState :: !(StrictTVar m (TentativeState blk))
, :: !(StrictTVar m (StrictMaybe (Header blk)))
, ChainDbEnv m blk -> StrictTVar m (Map IteratorKey (m ()))
cdbIterators :: !(StrictTVar m (Map IteratorKey (m ())))
, ChainDbEnv m blk
-> StrictTVar m (Map FollowerKey (FollowerHandle m blk))
cdbFollowers :: !(StrictTVar m (Map FollowerKey (FollowerHandle m blk)))
, ChainDbEnv m blk -> TopLevelConfig blk
cdbTopLevelConfig :: !(TopLevelConfig blk)
, ChainDbEnv m blk
-> StrictTVar m (WithFingerprint (InvalidBlocks blk))
cdbInvalid :: !(StrictTVar m (WithFingerprint (InvalidBlocks blk)))
, ChainDbEnv m blk -> StrictTVar m IteratorKey
cdbNextIteratorKey :: !(StrictTVar m IteratorKey)
, ChainDbEnv m blk -> StrictTVar m FollowerKey
cdbNextFollowerKey :: !(StrictTVar m FollowerKey)
, ChainDbEnv m blk -> StrictMVar m ()
cdbCopyLock :: !(StrictMVar m ())
, ChainDbEnv m blk -> Tracer m (TraceEvent blk)
cdbTracer :: !(Tracer m (TraceEvent blk))
, ChainDbEnv m blk -> Tracer m (LedgerDB' blk)
cdbTraceLedger :: !(Tracer m (LedgerDB' blk))
, ChainDbEnv m blk -> ResourceRegistry m
cdbRegistry :: !(ResourceRegistry m)
, ChainDbEnv m blk -> DiffTime
cdbGcDelay :: !DiffTime
, ChainDbEnv m blk -> DiffTime
cdbGcInterval :: !DiffTime
, ChainDbEnv m blk -> StrictTVar m (m ())
cdbKillBgThreads :: !(StrictTVar m (m ()))
, ChainDbEnv m blk -> ChunkInfo
cdbChunkInfo :: !ImmutableDB.ChunkInfo
, ChainDbEnv m blk -> blk -> Bool
cdbCheckIntegrity :: !(blk -> Bool)
, ChainDbEnv m blk -> CheckInFuture m blk
cdbCheckInFuture :: !(CheckInFuture m blk)
, ChainDbEnv m blk -> BlocksToAdd m blk
cdbBlocksToAdd :: !(BlocksToAdd m blk)
, ChainDbEnv m blk -> StrictTVar m (FutureBlocks m blk)
cdbFutureBlocks :: !(StrictTVar m (FutureBlocks m blk))
} deriving ((forall x. ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x)
-> (forall x. Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk)
-> Generic (ChainDbEnv m blk)
forall x. Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk
forall x. ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: * -> *) blk x.
Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk
forall (m :: * -> *) blk x.
ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x
$cto :: forall (m :: * -> *) blk x.
Rep (ChainDbEnv m blk) x -> ChainDbEnv m blk
$cfrom :: forall (m :: * -> *) blk x.
ChainDbEnv m blk -> Rep (ChainDbEnv m blk) x
Generic)
instance (IOLike m, LedgerSupportsProtocol blk)
=> NoThunks (ChainDbEnv m blk) where
showTypeOf :: Proxy (ChainDbEnv m blk) -> String
showTypeOf Proxy (ChainDbEnv m blk)
_ = String
"ChainDbEnv m " String -> String -> String
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (Proxy blk -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep (Proxy blk
forall k (t :: k). Proxy t
Proxy @blk))
data Internal m blk = Internal
{ Internal m blk -> m (WithOrigin SlotNo)
intCopyToImmutableDB :: m (WithOrigin SlotNo)
, Internal m blk -> SlotNo -> m ()
intGarbageCollect :: SlotNo -> m ()
, Internal m blk -> m ()
intUpdateLedgerSnapshots :: m ()
, Internal m blk -> m Void
intAddBlockRunner :: m Void
, Internal m blk -> StrictTVar m (m ())
intKillBgThreads :: StrictTVar m (m ())
}
newtype IteratorKey = IteratorKey Word
deriving stock (Int -> IteratorKey -> String -> String
[IteratorKey] -> String -> String
IteratorKey -> String
(Int -> IteratorKey -> String -> String)
-> (IteratorKey -> String)
-> ([IteratorKey] -> String -> String)
-> Show IteratorKey
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IteratorKey] -> String -> String
$cshowList :: [IteratorKey] -> String -> String
show :: IteratorKey -> String
$cshow :: IteratorKey -> String
showsPrec :: Int -> IteratorKey -> String -> String
$cshowsPrec :: Int -> IteratorKey -> String -> String
Show)
deriving newtype (IteratorKey -> IteratorKey -> Bool
(IteratorKey -> IteratorKey -> Bool)
-> (IteratorKey -> IteratorKey -> Bool) -> Eq IteratorKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IteratorKey -> IteratorKey -> Bool
$c/= :: IteratorKey -> IteratorKey -> Bool
== :: IteratorKey -> IteratorKey -> Bool
$c== :: IteratorKey -> IteratorKey -> Bool
Eq, Eq IteratorKey
Eq IteratorKey
-> (IteratorKey -> IteratorKey -> Ordering)
-> (IteratorKey -> IteratorKey -> Bool)
-> (IteratorKey -> IteratorKey -> Bool)
-> (IteratorKey -> IteratorKey -> Bool)
-> (IteratorKey -> IteratorKey -> Bool)
-> (IteratorKey -> IteratorKey -> IteratorKey)
-> (IteratorKey -> IteratorKey -> IteratorKey)
-> Ord IteratorKey
IteratorKey -> IteratorKey -> Bool
IteratorKey -> IteratorKey -> Ordering
IteratorKey -> IteratorKey -> IteratorKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: IteratorKey -> IteratorKey -> IteratorKey
$cmin :: IteratorKey -> IteratorKey -> IteratorKey
max :: IteratorKey -> IteratorKey -> IteratorKey
$cmax :: IteratorKey -> IteratorKey -> IteratorKey
>= :: IteratorKey -> IteratorKey -> Bool
$c>= :: IteratorKey -> IteratorKey -> Bool
> :: IteratorKey -> IteratorKey -> Bool
$c> :: IteratorKey -> IteratorKey -> Bool
<= :: IteratorKey -> IteratorKey -> Bool
$c<= :: IteratorKey -> IteratorKey -> Bool
< :: IteratorKey -> IteratorKey -> Bool
$c< :: IteratorKey -> IteratorKey -> Bool
compare :: IteratorKey -> IteratorKey -> Ordering
$ccompare :: IteratorKey -> IteratorKey -> Ordering
$cp1Ord :: Eq IteratorKey
Ord, Int -> IteratorKey
IteratorKey -> Int
IteratorKey -> [IteratorKey]
IteratorKey -> IteratorKey
IteratorKey -> IteratorKey -> [IteratorKey]
IteratorKey -> IteratorKey -> IteratorKey -> [IteratorKey]
(IteratorKey -> IteratorKey)
-> (IteratorKey -> IteratorKey)
-> (Int -> IteratorKey)
-> (IteratorKey -> Int)
-> (IteratorKey -> [IteratorKey])
-> (IteratorKey -> IteratorKey -> [IteratorKey])
-> (IteratorKey -> IteratorKey -> [IteratorKey])
-> (IteratorKey -> IteratorKey -> IteratorKey -> [IteratorKey])
-> Enum IteratorKey
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: IteratorKey -> IteratorKey -> IteratorKey -> [IteratorKey]
$cenumFromThenTo :: IteratorKey -> IteratorKey -> IteratorKey -> [IteratorKey]
enumFromTo :: IteratorKey -> IteratorKey -> [IteratorKey]
$cenumFromTo :: IteratorKey -> IteratorKey -> [IteratorKey]
enumFromThen :: IteratorKey -> IteratorKey -> [IteratorKey]
$cenumFromThen :: IteratorKey -> IteratorKey -> [IteratorKey]
enumFrom :: IteratorKey -> [IteratorKey]
$cenumFrom :: IteratorKey -> [IteratorKey]
fromEnum :: IteratorKey -> Int
$cfromEnum :: IteratorKey -> Int
toEnum :: Int -> IteratorKey
$ctoEnum :: Int -> IteratorKey
pred :: IteratorKey -> IteratorKey
$cpred :: IteratorKey -> IteratorKey
succ :: IteratorKey -> IteratorKey
$csucc :: IteratorKey -> IteratorKey
Enum, Context -> IteratorKey -> IO (Maybe ThunkInfo)
Proxy IteratorKey -> String
(Context -> IteratorKey -> IO (Maybe ThunkInfo))
-> (Context -> IteratorKey -> IO (Maybe ThunkInfo))
-> (Proxy IteratorKey -> String)
-> NoThunks IteratorKey
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy IteratorKey -> String
$cshowTypeOf :: Proxy IteratorKey -> String
wNoThunks :: Context -> IteratorKey -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> IteratorKey -> IO (Maybe ThunkInfo)
noThunks :: Context -> IteratorKey -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> IteratorKey -> IO (Maybe ThunkInfo)
NoThunks)
newtype FollowerKey = FollowerKey Word
deriving stock (Int -> FollowerKey -> String -> String
[FollowerKey] -> String -> String
FollowerKey -> String
(Int -> FollowerKey -> String -> String)
-> (FollowerKey -> String)
-> ([FollowerKey] -> String -> String)
-> Show FollowerKey
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FollowerKey] -> String -> String
$cshowList :: [FollowerKey] -> String -> String
show :: FollowerKey -> String
$cshow :: FollowerKey -> String
showsPrec :: Int -> FollowerKey -> String -> String
$cshowsPrec :: Int -> FollowerKey -> String -> String
Show)
deriving newtype (FollowerKey -> FollowerKey -> Bool
(FollowerKey -> FollowerKey -> Bool)
-> (FollowerKey -> FollowerKey -> Bool) -> Eq FollowerKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FollowerKey -> FollowerKey -> Bool
$c/= :: FollowerKey -> FollowerKey -> Bool
== :: FollowerKey -> FollowerKey -> Bool
$c== :: FollowerKey -> FollowerKey -> Bool
Eq, Eq FollowerKey
Eq FollowerKey
-> (FollowerKey -> FollowerKey -> Ordering)
-> (FollowerKey -> FollowerKey -> Bool)
-> (FollowerKey -> FollowerKey -> Bool)
-> (FollowerKey -> FollowerKey -> Bool)
-> (FollowerKey -> FollowerKey -> Bool)
-> (FollowerKey -> FollowerKey -> FollowerKey)
-> (FollowerKey -> FollowerKey -> FollowerKey)
-> Ord FollowerKey
FollowerKey -> FollowerKey -> Bool
FollowerKey -> FollowerKey -> Ordering
FollowerKey -> FollowerKey -> FollowerKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FollowerKey -> FollowerKey -> FollowerKey
$cmin :: FollowerKey -> FollowerKey -> FollowerKey
max :: FollowerKey -> FollowerKey -> FollowerKey
$cmax :: FollowerKey -> FollowerKey -> FollowerKey
>= :: FollowerKey -> FollowerKey -> Bool
$c>= :: FollowerKey -> FollowerKey -> Bool
> :: FollowerKey -> FollowerKey -> Bool
$c> :: FollowerKey -> FollowerKey -> Bool
<= :: FollowerKey -> FollowerKey -> Bool
$c<= :: FollowerKey -> FollowerKey -> Bool
< :: FollowerKey -> FollowerKey -> Bool
$c< :: FollowerKey -> FollowerKey -> Bool
compare :: FollowerKey -> FollowerKey -> Ordering
$ccompare :: FollowerKey -> FollowerKey -> Ordering
$cp1Ord :: Eq FollowerKey
Ord, Int -> FollowerKey
FollowerKey -> Int
FollowerKey -> [FollowerKey]
FollowerKey -> FollowerKey
FollowerKey -> FollowerKey -> [FollowerKey]
FollowerKey -> FollowerKey -> FollowerKey -> [FollowerKey]
(FollowerKey -> FollowerKey)
-> (FollowerKey -> FollowerKey)
-> (Int -> FollowerKey)
-> (FollowerKey -> Int)
-> (FollowerKey -> [FollowerKey])
-> (FollowerKey -> FollowerKey -> [FollowerKey])
-> (FollowerKey -> FollowerKey -> [FollowerKey])
-> (FollowerKey -> FollowerKey -> FollowerKey -> [FollowerKey])
-> Enum FollowerKey
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: FollowerKey -> FollowerKey -> FollowerKey -> [FollowerKey]
$cenumFromThenTo :: FollowerKey -> FollowerKey -> FollowerKey -> [FollowerKey]
enumFromTo :: FollowerKey -> FollowerKey -> [FollowerKey]
$cenumFromTo :: FollowerKey -> FollowerKey -> [FollowerKey]
enumFromThen :: FollowerKey -> FollowerKey -> [FollowerKey]
$cenumFromThen :: FollowerKey -> FollowerKey -> [FollowerKey]
enumFrom :: FollowerKey -> [FollowerKey]
$cenumFrom :: FollowerKey -> [FollowerKey]
fromEnum :: FollowerKey -> Int
$cfromEnum :: FollowerKey -> Int
toEnum :: Int -> FollowerKey
$ctoEnum :: Int -> FollowerKey
pred :: FollowerKey -> FollowerKey
$cpred :: FollowerKey -> FollowerKey
succ :: FollowerKey -> FollowerKey
$csucc :: FollowerKey -> FollowerKey
Enum, Context -> FollowerKey -> IO (Maybe ThunkInfo)
Proxy FollowerKey -> String
(Context -> FollowerKey -> IO (Maybe ThunkInfo))
-> (Context -> FollowerKey -> IO (Maybe ThunkInfo))
-> (Proxy FollowerKey -> String)
-> NoThunks FollowerKey
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy FollowerKey -> String
$cshowTypeOf :: Proxy FollowerKey -> String
wNoThunks :: Context -> FollowerKey -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> FollowerKey -> IO (Maybe ThunkInfo)
noThunks :: Context -> FollowerKey -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> FollowerKey -> IO (Maybe ThunkInfo)
NoThunks)
data FollowerHandle m blk = FollowerHandle
{ FollowerHandle m blk -> ChainType
fhChainType :: ChainType
, FollowerHandle m blk
-> Point blk -> AnchoredFragment (Header blk) -> STM m ()
fhSwitchFork :: Point blk -> AnchoredFragment (Header blk) -> STM m ()
, FollowerHandle m blk -> m ()
fhClose :: m ()
}
deriving Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
Proxy (FollowerHandle m blk) -> String
(Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo))
-> (Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo))
-> (Proxy (FollowerHandle m blk) -> String)
-> NoThunks (FollowerHandle m blk)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk.
Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk. Proxy (FollowerHandle m blk) -> String
showTypeOf :: Proxy (FollowerHandle m blk) -> String
$cshowTypeOf :: forall (m :: * -> *) blk. Proxy (FollowerHandle m blk) -> String
wNoThunks :: Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk.
Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (m :: * -> *) blk.
Context -> FollowerHandle m blk -> IO (Maybe ThunkInfo)
NoThunks via OnlyCheckWhnfNamed "FollowerHandle" (FollowerHandle m blk)
data FollowerState m blk b
= FollowerInit
| FollowerInImmutableDB
!(FollowerRollState blk)
!(ImmutableDB.Iterator m blk (Point blk, b))
| FollowerInMem !(FollowerRollState blk)
deriving ((forall x. FollowerState m blk b -> Rep (FollowerState m blk b) x)
-> (forall x.
Rep (FollowerState m blk b) x -> FollowerState m blk b)
-> Generic (FollowerState m blk b)
forall x. Rep (FollowerState m blk b) x -> FollowerState m blk b
forall x. FollowerState m blk b -> Rep (FollowerState m blk b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (m :: * -> *) blk b x.
Rep (FollowerState m blk b) x -> FollowerState m blk b
forall (m :: * -> *) blk b x.
FollowerState m blk b -> Rep (FollowerState m blk b) x
$cto :: forall (m :: * -> *) blk b x.
Rep (FollowerState m blk b) x -> FollowerState m blk b
$cfrom :: forall (m :: * -> *) blk b x.
FollowerState m blk b -> Rep (FollowerState m blk b) x
Generic, Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
Proxy (FollowerState m blk b) -> String
(Context -> FollowerState m blk b -> IO (Maybe ThunkInfo))
-> (Context -> FollowerState m blk b -> IO (Maybe ThunkInfo))
-> (Proxy (FollowerState m blk b) -> String)
-> NoThunks (FollowerState m blk b)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk b.
StandardHash blk =>
Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk b.
StandardHash blk =>
Proxy (FollowerState m blk b) -> String
showTypeOf :: Proxy (FollowerState m blk b) -> String
$cshowTypeOf :: forall (m :: * -> *) blk b.
StandardHash blk =>
Proxy (FollowerState m blk b) -> String
wNoThunks :: Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk b.
StandardHash blk =>
Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
noThunks :: Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (m :: * -> *) blk b.
StandardHash blk =>
Context -> FollowerState m blk b -> IO (Maybe ThunkInfo)
NoThunks)
data FollowerRollState blk
= RollBackTo !(Point blk)
| RollForwardFrom !(Point blk)
deriving (FollowerRollState blk -> FollowerRollState blk -> Bool
(FollowerRollState blk -> FollowerRollState blk -> Bool)
-> (FollowerRollState blk -> FollowerRollState blk -> Bool)
-> Eq (FollowerRollState blk)
forall blk.
StandardHash blk =>
FollowerRollState blk -> FollowerRollState blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FollowerRollState blk -> FollowerRollState blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
FollowerRollState blk -> FollowerRollState blk -> Bool
== :: FollowerRollState blk -> FollowerRollState blk -> Bool
$c== :: forall blk.
StandardHash blk =>
FollowerRollState blk -> FollowerRollState blk -> Bool
Eq, Int -> FollowerRollState blk -> String -> String
[FollowerRollState blk] -> String -> String
FollowerRollState blk -> String
(Int -> FollowerRollState blk -> String -> String)
-> (FollowerRollState blk -> String)
-> ([FollowerRollState blk] -> String -> String)
-> Show (FollowerRollState blk)
forall blk.
StandardHash blk =>
Int -> FollowerRollState blk -> String -> String
forall blk.
StandardHash blk =>
[FollowerRollState blk] -> String -> String
forall blk. StandardHash blk => FollowerRollState blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FollowerRollState blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[FollowerRollState blk] -> String -> String
show :: FollowerRollState blk -> String
$cshow :: forall blk. StandardHash blk => FollowerRollState blk -> String
showsPrec :: Int -> FollowerRollState blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> FollowerRollState blk -> String -> String
Show, (forall x. FollowerRollState blk -> Rep (FollowerRollState blk) x)
-> (forall x.
Rep (FollowerRollState blk) x -> FollowerRollState blk)
-> Generic (FollowerRollState blk)
forall x. Rep (FollowerRollState blk) x -> FollowerRollState blk
forall x. FollowerRollState blk -> Rep (FollowerRollState blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (FollowerRollState blk) x -> FollowerRollState blk
forall blk x.
FollowerRollState blk -> Rep (FollowerRollState blk) x
$cto :: forall blk x.
Rep (FollowerRollState blk) x -> FollowerRollState blk
$cfrom :: forall blk x.
FollowerRollState blk -> Rep (FollowerRollState blk) x
Generic, Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
Proxy (FollowerRollState blk) -> String
(Context -> FollowerRollState blk -> IO (Maybe ThunkInfo))
-> (Context -> FollowerRollState blk -> IO (Maybe ThunkInfo))
-> (Proxy (FollowerRollState blk) -> String)
-> NoThunks (FollowerRollState blk)
forall blk.
StandardHash blk =>
Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
forall blk.
StandardHash blk =>
Proxy (FollowerRollState blk) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (FollowerRollState blk) -> String
$cshowTypeOf :: forall blk.
StandardHash blk =>
Proxy (FollowerRollState blk) -> String
wNoThunks :: Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall blk.
StandardHash blk =>
Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall blk.
StandardHash blk =>
Context -> FollowerRollState blk -> IO (Maybe ThunkInfo)
NoThunks)
followerRollStatePoint :: FollowerRollState blk -> Point blk
followerRollStatePoint :: FollowerRollState blk -> Point blk
followerRollStatePoint (RollBackTo Point blk
pt) = Point blk
pt
followerRollStatePoint (RollForwardFrom Point blk
pt) = Point blk
pt
type InvalidBlocks blk = Map (HeaderHash blk) (InvalidBlockInfo blk)
data InvalidBlockInfo blk = InvalidBlockInfo
{ InvalidBlockInfo blk -> InvalidBlockReason blk
invalidBlockReason :: !(InvalidBlockReason blk)
, InvalidBlockInfo blk -> SlotNo
invalidBlockSlotNo :: !SlotNo
} deriving (InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
(InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool)
-> (InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool)
-> Eq (InvalidBlockInfo blk)
forall blk.
LedgerSupportsProtocol blk =>
InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
$c/= :: forall blk.
LedgerSupportsProtocol blk =>
InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
== :: InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
$c== :: forall blk.
LedgerSupportsProtocol blk =>
InvalidBlockInfo blk -> InvalidBlockInfo blk -> Bool
Eq, Int -> InvalidBlockInfo blk -> String -> String
[InvalidBlockInfo blk] -> String -> String
InvalidBlockInfo blk -> String
(Int -> InvalidBlockInfo blk -> String -> String)
-> (InvalidBlockInfo blk -> String)
-> ([InvalidBlockInfo blk] -> String -> String)
-> Show (InvalidBlockInfo blk)
forall blk.
LedgerSupportsProtocol blk =>
Int -> InvalidBlockInfo blk -> String -> String
forall blk.
LedgerSupportsProtocol blk =>
[InvalidBlockInfo blk] -> String -> String
forall blk.
LedgerSupportsProtocol blk =>
InvalidBlockInfo blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InvalidBlockInfo blk] -> String -> String
$cshowList :: forall blk.
LedgerSupportsProtocol blk =>
[InvalidBlockInfo blk] -> String -> String
show :: InvalidBlockInfo blk -> String
$cshow :: forall blk.
LedgerSupportsProtocol blk =>
InvalidBlockInfo blk -> String
showsPrec :: Int -> InvalidBlockInfo blk -> String -> String
$cshowsPrec :: forall blk.
LedgerSupportsProtocol blk =>
Int -> InvalidBlockInfo blk -> String -> String
Show, (forall x. InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x)
-> (forall x. Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk)
-> Generic (InvalidBlockInfo blk)
forall x. Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk
forall x. InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk
forall blk x. InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x
$cto :: forall blk x. Rep (InvalidBlockInfo blk) x -> InvalidBlockInfo blk
$cfrom :: forall blk x. InvalidBlockInfo blk -> Rep (InvalidBlockInfo blk) x
Generic, Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
Proxy (InvalidBlockInfo blk) -> String
(Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo))
-> (Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo))
-> (Proxy (InvalidBlockInfo blk) -> String)
-> NoThunks (InvalidBlockInfo blk)
forall blk.
LedgerSupportsProtocol blk =>
Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
forall blk.
LedgerSupportsProtocol blk =>
Proxy (InvalidBlockInfo blk) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy (InvalidBlockInfo blk) -> String
$cshowTypeOf :: forall blk.
LedgerSupportsProtocol blk =>
Proxy (InvalidBlockInfo blk) -> String
wNoThunks :: Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall blk.
LedgerSupportsProtocol blk =>
Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall blk.
LedgerSupportsProtocol blk =>
Context -> InvalidBlockInfo blk -> IO (Maybe ThunkInfo)
NoThunks)
type FutureBlocks m blk = Map (HeaderHash blk) (Header blk, InvalidBlockPunishment m)
newtype BlocksToAdd m blk = BlocksToAdd (TBQueue m (BlockToAdd m blk))
deriving Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
Proxy (BlocksToAdd m blk) -> String
(Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo))
-> (Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo))
-> (Proxy (BlocksToAdd m blk) -> String)
-> NoThunks (BlocksToAdd m blk)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
forall (m :: * -> *) blk.
Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
forall (m :: * -> *) blk. Proxy (BlocksToAdd m blk) -> String
showTypeOf :: Proxy (BlocksToAdd m blk) -> String
$cshowTypeOf :: forall (m :: * -> *) blk. Proxy (BlocksToAdd m blk) -> String
wNoThunks :: Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall (m :: * -> *) blk.
Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
noThunks :: Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
$cnoThunks :: forall (m :: * -> *) blk.
Context -> BlocksToAdd m blk -> IO (Maybe ThunkInfo)
NoThunks via OnlyCheckWhnfNamed "BlocksToAdd" (BlocksToAdd m blk)
data BlockToAdd m blk = BlockToAdd
{ BlockToAdd m blk -> InvalidBlockPunishment m
blockPunish :: !(InvalidBlockPunishment m)
, BlockToAdd m blk -> blk
blockToAdd :: !blk
, BlockToAdd m blk -> StrictTMVar m Bool
varBlockWrittenToDisk :: !(StrictTMVar m Bool)
, BlockToAdd m blk -> StrictTMVar m (Point blk)
varBlockProcessed :: !(StrictTMVar m (Point blk))
}
newBlocksToAdd :: IOLike m => Word -> m (BlocksToAdd m blk)
newBlocksToAdd :: Word -> m (BlocksToAdd m blk)
newBlocksToAdd Word
queueSize = TBQueue m (BlockToAdd m blk) -> BlocksToAdd m blk
forall (m :: * -> *) blk.
TBQueue m (BlockToAdd m blk) -> BlocksToAdd m blk
BlocksToAdd (TBQueue m (BlockToAdd m blk) -> BlocksToAdd m blk)
-> m (TBQueue m (BlockToAdd m blk)) -> m (BlocksToAdd m blk)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
STM m (TBQueue m (BlockToAdd m blk))
-> m (TBQueue m (BlockToAdd m blk))
forall (m :: * -> *) a.
(MonadSTM m, HasCallStack) =>
STM m a -> m a
atomically (Natural -> STM m (TBQueue m (BlockToAdd m blk))
forall (m :: * -> *) a.
MonadSTM m =>
Natural -> STM m (TBQueue m a)
newTBQueue (Word -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
queueSize))
addBlockToAdd
:: (IOLike m, HasHeader blk)
=> Tracer m (TraceAddBlockEvent blk)
-> BlocksToAdd m blk
-> InvalidBlockPunishment m
-> blk
-> m (AddBlockPromise m blk)
addBlockToAdd :: Tracer m (TraceAddBlockEvent blk)
-> BlocksToAdd m blk
-> InvalidBlockPunishment m
-> blk
-> m (AddBlockPromise m blk)
addBlockToAdd Tracer m (TraceAddBlockEvent blk)
tracer (BlocksToAdd TBQueue m (BlockToAdd m blk)
queue) InvalidBlockPunishment m
punish blk
blk = do
StrictTMVar m Bool
varBlockWrittenToDisk <- m (StrictTMVar m Bool)
forall (m :: * -> *) a. MonadSTM m => m (StrictTMVar m a)
newEmptyTMVarIO
StrictTMVar m (Point blk)
varBlockProcessed <- m (StrictTMVar m (Point blk))
forall (m :: * -> *) a. MonadSTM m => m (StrictTMVar m a)
newEmptyTMVarIO
let !toAdd :: BlockToAdd m blk
toAdd = BlockToAdd :: forall (m :: * -> *) blk.
InvalidBlockPunishment m
-> blk
-> StrictTMVar m Bool
-> StrictTMVar m (Point blk)
-> BlockToAdd m blk
BlockToAdd
{ blockPunish :: InvalidBlockPunishment m
blockPunish = InvalidBlockPunishment m
punish
, blockToAdd :: blk
blockToAdd = blk
blk
, StrictTMVar m Bool
varBlockWrittenToDisk :: StrictTMVar m Bool
varBlockWrittenToDisk :: StrictTMVar m Bool
varBlockWrittenToDisk
, StrictTMVar m (Point blk)
varBlockProcessed :: StrictTMVar m (Point blk)
varBlockProcessed :: StrictTMVar m (Point blk)
varBlockProcessed
}
Tracer m (TraceAddBlockEvent blk) -> TraceAddBlockEvent blk -> m ()
forall (m :: * -> *) a. Tracer m a -> a -> m ()
traceWith Tracer m (TraceAddBlockEvent blk)
tracer (TraceAddBlockEvent blk -> m ()) -> TraceAddBlockEvent blk -> m ()
forall a b. (a -> b) -> a -> b
$ RealPoint blk -> Enclosing' Word -> TraceAddBlockEvent blk
forall blk.
RealPoint blk -> Enclosing' Word -> TraceAddBlockEvent blk
AddedBlockToQueue (blk -> RealPoint blk
forall blk. HasHeader blk => blk -> RealPoint blk
blockRealPoint blk
blk) Enclosing' Word
forall a. Enclosing' a
RisingEdge
Natural
queueSize <- STM m Natural -> m Natural
forall (m :: * -> *) a.
(MonadSTM m, HasCallStack) =>
STM m a -> m a
atomically (STM m Natural -> m Natural) -> STM m Natural -> m Natural
forall a b. (a -> b) -> a -> b
$ do
TBQueue m (BlockToAdd m blk) -> BlockToAdd m blk -> STM m ()
forall (m :: * -> *) a. MonadSTM m => TBQueue m a -> a -> STM m ()
writeTBQueue TBQueue m (BlockToAdd m blk)
queue BlockToAdd m blk
toAdd
TBQueue m (BlockToAdd m blk) -> STM m Natural
forall (m :: * -> *) a. MonadSTM m => TBQueue m a -> STM m Natural
lengthTBQueue TBQueue m (BlockToAdd m blk)
queue
Tracer m (TraceAddBlockEvent blk) -> TraceAddBlockEvent blk -> m ()
forall (m :: * -> *) a. Tracer m a -> a -> m ()
traceWith Tracer m (TraceAddBlockEvent blk)
tracer (TraceAddBlockEvent blk -> m ()) -> TraceAddBlockEvent blk -> m ()
forall a b. (a -> b) -> a -> b
$
RealPoint blk -> Enclosing' Word -> TraceAddBlockEvent blk
forall blk.
RealPoint blk -> Enclosing' Word -> TraceAddBlockEvent blk
AddedBlockToQueue (blk -> RealPoint blk
forall blk. HasHeader blk => blk -> RealPoint blk
blockRealPoint blk
blk) (Word -> Enclosing' Word
forall a. a -> Enclosing' a
FallingEdgeWith (Natural -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Natural
queueSize))
AddBlockPromise m blk -> m (AddBlockPromise m blk)
forall (m :: * -> *) a. Monad m => a -> m a
return AddBlockPromise :: forall (m :: * -> *) blk.
STM m Bool -> STM m (Point blk) -> AddBlockPromise m blk
AddBlockPromise
{ blockWrittenToDisk :: STM m Bool
blockWrittenToDisk = StrictTMVar m Bool -> STM m Bool
forall (m :: * -> *) a. MonadSTM m => StrictTMVar m a -> STM m a
readTMVar StrictTMVar m Bool
varBlockWrittenToDisk
, blockProcessed :: STM m (Point blk)
blockProcessed = StrictTMVar m (Point blk) -> STM m (Point blk)
forall (m :: * -> *) a. MonadSTM m => StrictTMVar m a -> STM m a
readTMVar StrictTMVar m (Point blk)
varBlockProcessed
}
getBlockToAdd :: IOLike m => BlocksToAdd m blk -> m (BlockToAdd m blk)
getBlockToAdd :: BlocksToAdd m blk -> m (BlockToAdd m blk)
getBlockToAdd (BlocksToAdd TBQueue m (BlockToAdd m blk)
queue) = STM m (BlockToAdd m blk) -> m (BlockToAdd m blk)
forall (m :: * -> *) a.
(MonadSTM m, HasCallStack) =>
STM m a -> m a
atomically (STM m (BlockToAdd m blk) -> m (BlockToAdd m blk))
-> STM m (BlockToAdd m blk) -> m (BlockToAdd m blk)
forall a b. (a -> b) -> a -> b
$ TBQueue m (BlockToAdd m blk) -> STM m (BlockToAdd m blk)
forall (m :: * -> *) a. MonadSTM m => TBQueue m a -> STM m a
readTBQueue TBQueue m (BlockToAdd m blk)
queue
data TraceEvent blk
= TraceAddBlockEvent (TraceAddBlockEvent blk)
| TraceFollowerEvent (TraceFollowerEvent blk)
| TraceCopyToImmutableDBEvent (TraceCopyToImmutableDBEvent blk)
| TraceGCEvent (TraceGCEvent blk)
| TraceInitChainSelEvent (TraceInitChainSelEvent blk)
| TraceOpenEvent (TraceOpenEvent blk)
| TraceIteratorEvent (TraceIteratorEvent blk)
| TraceLedgerEvent (LgrDB.TraceEvent blk)
| TraceLedgerReplayEvent (LgrDB.TraceReplayEvent blk)
| TraceImmutableDBEvent (ImmutableDB.TraceEvent blk)
| TraceVolatileDBEvent (VolatileDB.TraceEvent blk)
deriving ((forall x. TraceEvent blk -> Rep (TraceEvent blk) x)
-> (forall x. Rep (TraceEvent blk) x -> TraceEvent blk)
-> Generic (TraceEvent blk)
forall x. Rep (TraceEvent blk) x -> TraceEvent blk
forall x. TraceEvent blk -> Rep (TraceEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (TraceEvent blk) x -> TraceEvent blk
forall blk x. TraceEvent blk -> Rep (TraceEvent blk) x
$cto :: forall blk x. Rep (TraceEvent blk) x -> TraceEvent blk
$cfrom :: forall blk x. TraceEvent blk -> Rep (TraceEvent blk) x
Generic)
deriving instance
( HasHeader blk
, Eq (Header blk)
, LedgerSupportsProtocol blk
, InspectLedger blk
) => Eq (TraceEvent blk)
deriving instance
( HasHeader blk
, Show (Header blk)
, LedgerSupportsProtocol blk
, InspectLedger blk
) => Show (TraceEvent blk)
data TraceOpenEvent blk =
StartedOpeningDB
| OpenedDB
(Point blk)
(Point blk)
| ClosedDB
(Point blk)
(Point blk)
| StartedOpeningImmutableDB
| OpenedImmutableDB
(Point blk)
ImmutableDB.ChunkNo
| StartedOpeningVolatileDB
| OpenedVolatileDB
| StartedOpeningLgrDB
| OpenedLgrDB
deriving ((forall x. TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x)
-> (forall x. Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk)
-> Generic (TraceOpenEvent blk)
forall x. Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk
forall x. TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk
forall blk x. TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x
$cto :: forall blk x. Rep (TraceOpenEvent blk) x -> TraceOpenEvent blk
$cfrom :: forall blk x. TraceOpenEvent blk -> Rep (TraceOpenEvent blk) x
Generic, TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
(TraceOpenEvent blk -> TraceOpenEvent blk -> Bool)
-> (TraceOpenEvent blk -> TraceOpenEvent blk -> Bool)
-> Eq (TraceOpenEvent blk)
forall blk.
StandardHash blk =>
TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
== :: TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
$c== :: forall blk.
StandardHash blk =>
TraceOpenEvent blk -> TraceOpenEvent blk -> Bool
Eq, Int -> TraceOpenEvent blk -> String -> String
[TraceOpenEvent blk] -> String -> String
TraceOpenEvent blk -> String
(Int -> TraceOpenEvent blk -> String -> String)
-> (TraceOpenEvent blk -> String)
-> ([TraceOpenEvent blk] -> String -> String)
-> Show (TraceOpenEvent blk)
forall blk.
StandardHash blk =>
Int -> TraceOpenEvent blk -> String -> String
forall blk.
StandardHash blk =>
[TraceOpenEvent blk] -> String -> String
forall blk. StandardHash blk => TraceOpenEvent blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TraceOpenEvent blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[TraceOpenEvent blk] -> String -> String
show :: TraceOpenEvent blk -> String
$cshow :: forall blk. StandardHash blk => TraceOpenEvent blk -> String
showsPrec :: Int -> TraceOpenEvent blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> TraceOpenEvent blk -> String -> String
Show)
data NewTipInfo blk = NewTipInfo {
NewTipInfo blk -> RealPoint blk
newTipPoint :: RealPoint blk
, NewTipInfo blk -> EpochNo
newTipEpoch :: EpochNo
, NewTipInfo blk -> Word64
newTipSlotInEpoch :: Word64
, NewTipInfo blk -> RealPoint blk
newTipTrigger :: RealPoint blk
}
deriving (NewTipInfo blk -> NewTipInfo blk -> Bool
(NewTipInfo blk -> NewTipInfo blk -> Bool)
-> (NewTipInfo blk -> NewTipInfo blk -> Bool)
-> Eq (NewTipInfo blk)
forall blk.
StandardHash blk =>
NewTipInfo blk -> NewTipInfo blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewTipInfo blk -> NewTipInfo blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
NewTipInfo blk -> NewTipInfo blk -> Bool
== :: NewTipInfo blk -> NewTipInfo blk -> Bool
$c== :: forall blk.
StandardHash blk =>
NewTipInfo blk -> NewTipInfo blk -> Bool
Eq, Int -> NewTipInfo blk -> String -> String
[NewTipInfo blk] -> String -> String
NewTipInfo blk -> String
(Int -> NewTipInfo blk -> String -> String)
-> (NewTipInfo blk -> String)
-> ([NewTipInfo blk] -> String -> String)
-> Show (NewTipInfo blk)
forall blk.
StandardHash blk =>
Int -> NewTipInfo blk -> String -> String
forall blk.
StandardHash blk =>
[NewTipInfo blk] -> String -> String
forall blk. StandardHash blk => NewTipInfo blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NewTipInfo blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[NewTipInfo blk] -> String -> String
show :: NewTipInfo blk -> String
$cshow :: forall blk. StandardHash blk => NewTipInfo blk -> String
showsPrec :: Int -> NewTipInfo blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> NewTipInfo blk -> String -> String
Show, (forall x. NewTipInfo blk -> Rep (NewTipInfo blk) x)
-> (forall x. Rep (NewTipInfo blk) x -> NewTipInfo blk)
-> Generic (NewTipInfo blk)
forall x. Rep (NewTipInfo blk) x -> NewTipInfo blk
forall x. NewTipInfo blk -> Rep (NewTipInfo blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (NewTipInfo blk) x -> NewTipInfo blk
forall blk x. NewTipInfo blk -> Rep (NewTipInfo blk) x
$cto :: forall blk x. Rep (NewTipInfo blk) x -> NewTipInfo blk
$cfrom :: forall blk x. NewTipInfo blk -> Rep (NewTipInfo blk) x
Generic)
data TraceAddBlockEvent blk =
IgnoreBlockOlderThanK (RealPoint blk)
| IgnoreBlockAlreadyInVolatileDB (RealPoint blk)
| IgnoreInvalidBlock (RealPoint blk) (InvalidBlockReason blk)
| AddedBlockToQueue (RealPoint blk) (Enclosing' Word)
| PoppedBlockFromQueue (Enclosing' (RealPoint blk))
| BlockInTheFuture (RealPoint blk) SlotNo
| AddedBlockToVolatileDB (RealPoint blk) BlockNo IsEBB Enclosing
| TryAddToCurrentChain (RealPoint blk)
| TrySwitchToAFork (RealPoint blk) (ChainDiff (HeaderFields blk))
| StoreButDontChange (RealPoint blk)
| AddedToCurrentChain
[LedgerEvent blk]
(NewTipInfo blk)
(AnchoredFragment (Header blk))
(AnchoredFragment (Header blk))
| SwitchedToAFork
[LedgerEvent blk]
(NewTipInfo blk)
(AnchoredFragment (Header blk))
(AnchoredFragment (Header blk))
| AddBlockValidation (TraceValidationEvent blk)
| ChainSelectionForFutureBlock (RealPoint blk)
| PipeliningEvent (TracePipeliningEvent blk)
| ChangingSelection (Point blk)
deriving ((forall x.
TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x)
-> (forall x.
Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk)
-> Generic (TraceAddBlockEvent blk)
forall x. Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk
forall x. TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk
forall blk x.
TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x
$cto :: forall blk x.
Rep (TraceAddBlockEvent blk) x -> TraceAddBlockEvent blk
$cfrom :: forall blk x.
TraceAddBlockEvent blk -> Rep (TraceAddBlockEvent blk) x
Generic)
deriving instance
( HasHeader blk
, Eq (Header blk)
, LedgerSupportsProtocol blk
, InspectLedger blk
) => Eq (TraceAddBlockEvent blk)
deriving instance
( HasHeader blk
, Show (Header blk)
, LedgerSupportsProtocol blk
, InspectLedger blk
) => Show (TraceAddBlockEvent blk)
data TraceValidationEvent blk =
InvalidBlock
(ExtValidationError blk)
(RealPoint blk)
| ValidCandidate (AnchoredFragment (Header blk))
| CandidateContainsFutureBlocks
(AnchoredFragment (Header blk))
[Header blk]
| CandidateContainsFutureBlocksExceedingClockSkew
(AnchoredFragment (Header blk))
[Header blk]
| UpdateLedgerDbTraceEvent (UpdateLedgerDbTraceEvent blk)
deriving ((forall x.
TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x)
-> (forall x.
Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk)
-> Generic (TraceValidationEvent blk)
forall x.
Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk
forall x.
TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk
forall blk x.
TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x
$cto :: forall blk x.
Rep (TraceValidationEvent blk) x -> TraceValidationEvent blk
$cfrom :: forall blk x.
TraceValidationEvent blk -> Rep (TraceValidationEvent blk) x
Generic)
deriving instance
( HasHeader blk
, Eq (Header blk)
, LedgerSupportsProtocol blk
) => Eq (TraceValidationEvent blk)
deriving instance
( Show (Header blk)
, LedgerSupportsProtocol blk
) => Show (TraceValidationEvent blk)
data TracePipeliningEvent blk =
(Header blk) Enclosing
| (Header blk)
| (Header blk)
deriving stock instance Eq (Header blk) => Eq (TracePipeliningEvent blk)
deriving stock instance Show (Header blk) => Show (TracePipeliningEvent blk)
data TraceInitChainSelEvent blk =
StartedInitChainSelection
| InitalChainSelected
| InitChainSelValidation (TraceValidationEvent blk)
deriving ((forall x.
TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x)
-> (forall x.
Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk)
-> Generic (TraceInitChainSelEvent blk)
forall x.
Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk
forall x.
TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk
forall blk x.
TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x
$cto :: forall blk x.
Rep (TraceInitChainSelEvent blk) x -> TraceInitChainSelEvent blk
$cfrom :: forall blk x.
TraceInitChainSelEvent blk -> Rep (TraceInitChainSelEvent blk) x
Generic)
deriving instance
( HasHeader blk
, Eq (Header blk)
, LedgerSupportsProtocol blk
) => Eq (TraceInitChainSelEvent blk)
deriving instance
( Show (Header blk)
, LedgerSupportsProtocol blk
) => Show (TraceInitChainSelEvent blk)
data TraceFollowerEvent blk =
NewFollower
| FollowerNoLongerInMem (FollowerRollState blk)
| FollowerSwitchToMem
(Point blk)
(WithOrigin SlotNo)
| FollowerNewImmIterator
(Point blk)
(WithOrigin SlotNo)
deriving ((forall x.
TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x)
-> (forall x.
Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk)
-> Generic (TraceFollowerEvent blk)
forall x. Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk
forall x. TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk
forall blk x.
TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x
$cto :: forall blk x.
Rep (TraceFollowerEvent blk) x -> TraceFollowerEvent blk
$cfrom :: forall blk x.
TraceFollowerEvent blk -> Rep (TraceFollowerEvent blk) x
Generic, TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
(TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool)
-> (TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool)
-> Eq (TraceFollowerEvent blk)
forall blk.
StandardHash blk =>
TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
== :: TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
$c== :: forall blk.
StandardHash blk =>
TraceFollowerEvent blk -> TraceFollowerEvent blk -> Bool
Eq, Int -> TraceFollowerEvent blk -> String -> String
[TraceFollowerEvent blk] -> String -> String
TraceFollowerEvent blk -> String
(Int -> TraceFollowerEvent blk -> String -> String)
-> (TraceFollowerEvent blk -> String)
-> ([TraceFollowerEvent blk] -> String -> String)
-> Show (TraceFollowerEvent blk)
forall blk.
StandardHash blk =>
Int -> TraceFollowerEvent blk -> String -> String
forall blk.
StandardHash blk =>
[TraceFollowerEvent blk] -> String -> String
forall blk. StandardHash blk => TraceFollowerEvent blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TraceFollowerEvent blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[TraceFollowerEvent blk] -> String -> String
show :: TraceFollowerEvent blk -> String
$cshow :: forall blk. StandardHash blk => TraceFollowerEvent blk -> String
showsPrec :: Int -> TraceFollowerEvent blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> TraceFollowerEvent blk -> String -> String
Show)
data TraceCopyToImmutableDBEvent blk
= CopiedBlockToImmutableDB (Point blk)
| NoBlocksToCopyToImmutableDB
deriving ((forall x.
TraceCopyToImmutableDBEvent blk
-> Rep (TraceCopyToImmutableDBEvent blk) x)
-> (forall x.
Rep (TraceCopyToImmutableDBEvent blk) x
-> TraceCopyToImmutableDBEvent blk)
-> Generic (TraceCopyToImmutableDBEvent blk)
forall x.
Rep (TraceCopyToImmutableDBEvent blk) x
-> TraceCopyToImmutableDBEvent blk
forall x.
TraceCopyToImmutableDBEvent blk
-> Rep (TraceCopyToImmutableDBEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceCopyToImmutableDBEvent blk) x
-> TraceCopyToImmutableDBEvent blk
forall blk x.
TraceCopyToImmutableDBEvent blk
-> Rep (TraceCopyToImmutableDBEvent blk) x
$cto :: forall blk x.
Rep (TraceCopyToImmutableDBEvent blk) x
-> TraceCopyToImmutableDBEvent blk
$cfrom :: forall blk x.
TraceCopyToImmutableDBEvent blk
-> Rep (TraceCopyToImmutableDBEvent blk) x
Generic, TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
(TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool)
-> (TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool)
-> Eq (TraceCopyToImmutableDBEvent blk)
forall blk.
StandardHash blk =>
TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
== :: TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
$c== :: forall blk.
StandardHash blk =>
TraceCopyToImmutableDBEvent blk
-> TraceCopyToImmutableDBEvent blk -> Bool
Eq, Int -> TraceCopyToImmutableDBEvent blk -> String -> String
[TraceCopyToImmutableDBEvent blk] -> String -> String
TraceCopyToImmutableDBEvent blk -> String
(Int -> TraceCopyToImmutableDBEvent blk -> String -> String)
-> (TraceCopyToImmutableDBEvent blk -> String)
-> ([TraceCopyToImmutableDBEvent blk] -> String -> String)
-> Show (TraceCopyToImmutableDBEvent blk)
forall blk.
StandardHash blk =>
Int -> TraceCopyToImmutableDBEvent blk -> String -> String
forall blk.
StandardHash blk =>
[TraceCopyToImmutableDBEvent blk] -> String -> String
forall blk.
StandardHash blk =>
TraceCopyToImmutableDBEvent blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TraceCopyToImmutableDBEvent blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[TraceCopyToImmutableDBEvent blk] -> String -> String
show :: TraceCopyToImmutableDBEvent blk -> String
$cshow :: forall blk.
StandardHash blk =>
TraceCopyToImmutableDBEvent blk -> String
showsPrec :: Int -> TraceCopyToImmutableDBEvent blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> TraceCopyToImmutableDBEvent blk -> String -> String
Show)
data TraceGCEvent blk
= ScheduledGC SlotNo Time
| PerformedGC SlotNo
deriving ((forall x. TraceGCEvent blk -> Rep (TraceGCEvent blk) x)
-> (forall x. Rep (TraceGCEvent blk) x -> TraceGCEvent blk)
-> Generic (TraceGCEvent blk)
forall x. Rep (TraceGCEvent blk) x -> TraceGCEvent blk
forall x. TraceGCEvent blk -> Rep (TraceGCEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x. Rep (TraceGCEvent blk) x -> TraceGCEvent blk
forall blk x. TraceGCEvent blk -> Rep (TraceGCEvent blk) x
$cto :: forall blk x. Rep (TraceGCEvent blk) x -> TraceGCEvent blk
$cfrom :: forall blk x. TraceGCEvent blk -> Rep (TraceGCEvent blk) x
Generic, TraceGCEvent blk -> TraceGCEvent blk -> Bool
(TraceGCEvent blk -> TraceGCEvent blk -> Bool)
-> (TraceGCEvent blk -> TraceGCEvent blk -> Bool)
-> Eq (TraceGCEvent blk)
forall blk. TraceGCEvent blk -> TraceGCEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceGCEvent blk -> TraceGCEvent blk -> Bool
$c/= :: forall blk. TraceGCEvent blk -> TraceGCEvent blk -> Bool
== :: TraceGCEvent blk -> TraceGCEvent blk -> Bool
$c== :: forall blk. TraceGCEvent blk -> TraceGCEvent blk -> Bool
Eq, Int -> TraceGCEvent blk -> String -> String
[TraceGCEvent blk] -> String -> String
TraceGCEvent blk -> String
(Int -> TraceGCEvent blk -> String -> String)
-> (TraceGCEvent blk -> String)
-> ([TraceGCEvent blk] -> String -> String)
-> Show (TraceGCEvent blk)
forall blk. Int -> TraceGCEvent blk -> String -> String
forall blk. [TraceGCEvent blk] -> String -> String
forall blk. TraceGCEvent blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TraceGCEvent blk] -> String -> String
$cshowList :: forall blk. [TraceGCEvent blk] -> String -> String
show :: TraceGCEvent blk -> String
$cshow :: forall blk. TraceGCEvent blk -> String
showsPrec :: Int -> TraceGCEvent blk -> String -> String
$cshowsPrec :: forall blk. Int -> TraceGCEvent blk -> String -> String
Show)
data TraceIteratorEvent blk
= UnknownRangeRequested (UnknownRange blk)
| StreamFromVolatileDB
(StreamFrom blk)
(StreamTo blk)
[RealPoint blk]
| StreamFromImmutableDB
(StreamFrom blk)
(StreamTo blk)
| StreamFromBoth
(StreamFrom blk)
(StreamTo blk)
[RealPoint blk]
| BlockMissingFromVolatileDB (RealPoint blk)
| BlockWasCopiedToImmutableDB (RealPoint blk)
| BlockGCedFromVolatileDB (RealPoint blk)
| SwitchBackToVolatileDB
deriving ((forall x.
TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x)
-> (forall x.
Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk)
-> Generic (TraceIteratorEvent blk)
forall x. Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk
forall x. TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall blk x.
Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk
forall blk x.
TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x
$cto :: forall blk x.
Rep (TraceIteratorEvent blk) x -> TraceIteratorEvent blk
$cfrom :: forall blk x.
TraceIteratorEvent blk -> Rep (TraceIteratorEvent blk) x
Generic, TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
(TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool)
-> (TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool)
-> Eq (TraceIteratorEvent blk)
forall blk.
StandardHash blk =>
TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
$c/= :: forall blk.
StandardHash blk =>
TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
== :: TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
$c== :: forall blk.
StandardHash blk =>
TraceIteratorEvent blk -> TraceIteratorEvent blk -> Bool
Eq, Int -> TraceIteratorEvent blk -> String -> String
[TraceIteratorEvent blk] -> String -> String
TraceIteratorEvent blk -> String
(Int -> TraceIteratorEvent blk -> String -> String)
-> (TraceIteratorEvent blk -> String)
-> ([TraceIteratorEvent blk] -> String -> String)
-> Show (TraceIteratorEvent blk)
forall blk.
StandardHash blk =>
Int -> TraceIteratorEvent blk -> String -> String
forall blk.
StandardHash blk =>
[TraceIteratorEvent blk] -> String -> String
forall blk. StandardHash blk => TraceIteratorEvent blk -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TraceIteratorEvent blk] -> String -> String
$cshowList :: forall blk.
StandardHash blk =>
[TraceIteratorEvent blk] -> String -> String
show :: TraceIteratorEvent blk -> String
$cshow :: forall blk. StandardHash blk => TraceIteratorEvent blk -> String
showsPrec :: Int -> TraceIteratorEvent blk -> String -> String
$cshowsPrec :: forall blk.
StandardHash blk =>
Int -> TraceIteratorEvent blk -> String -> String
Show)