{-# LANGUAGE FlexibleContexts #-}
module Ouroboros.Consensus.Node.Run (
ImmutableDbSerialiseConstraints
, LgrDbSerialiseConstraints
, SerialiseDiskConstraints
, VolatileDbSerialiseConstraints
, SerialiseNodeToNodeConstraints (..)
, SerialiseNodeToClientConstraints
, RunNode
) where
import Data.Typeable (Typeable)
import Ouroboros.Network.Block (Serialised)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Config.SupportsNode
import Ouroboros.Consensus.HardFork.Abstract
import Ouroboros.Consensus.Ledger.CommonProtocolParams
import Ouroboros.Consensus.Ledger.Inspect
import Ouroboros.Consensus.Ledger.Query
import Ouroboros.Consensus.Ledger.SupportsMempool
import Ouroboros.Consensus.Ledger.SupportsPeerSelection
import Ouroboros.Consensus.Ledger.SupportsProtocol
import Ouroboros.Consensus.Node.InitStorage
import Ouroboros.Consensus.Node.NetworkProtocolVersion
import Ouroboros.Consensus.Node.Serialisation
import Ouroboros.Consensus.Util (ShowProxy)
import Ouroboros.Consensus.Storage.ChainDB
(ImmutableDbSerialiseConstraints,
LgrDbSerialiseConstraints, SerialiseDiskConstraints,
VolatileDbSerialiseConstraints)
import Ouroboros.Consensus.Storage.Serialisation
class ( ConvertRawHash blk
, SerialiseNodeToNode blk blk
, SerialiseNodeToNode blk (Header blk)
, SerialiseNodeToNode blk (Serialised blk)
, SerialiseNodeToNode blk (SerialisedHeader blk)
, SerialiseNodeToNode blk (GenTx blk)
, SerialiseNodeToNode blk (GenTxId blk)
) => SerialiseNodeToNodeConstraints blk where
estimateBlockSize :: Header blk -> SizeInBytes
class ( Typeable blk
, ConvertRawHash blk
, SerialiseNodeToClient blk blk
, SerialiseNodeToClient blk (Serialised blk)
, SerialiseNodeToClient blk (GenTx blk)
, SerialiseNodeToClient blk (GenTxId blk)
, SerialiseNodeToClient blk SlotNo
, SerialiseNodeToClient blk (ApplyTxErr blk)
, SerialiseNodeToClient blk (SomeSecond BlockQuery blk)
, SerialiseResult blk (BlockQuery blk)
) => SerialiseNodeToClientConstraints blk
class ( LedgerSupportsProtocol blk
, InspectLedger blk
, HasHardForkHistory blk
, LedgerSupportsMempool blk
, HasTxId (GenTx blk)
, QueryLedger blk
, SupportedNetworkProtocolVersion blk
, ConfigSupportsNode blk
, ConvertRawHash blk
, CommonProtocolParams blk
, HasBinaryBlockInfo blk
, SerialiseDiskConstraints blk
, SerialiseNodeToNodeConstraints blk
, SerialiseNodeToClientConstraints blk
, LedgerSupportsPeerSelection blk
, NodeInitStorage blk
, BlockSupportsMetrics blk
, Show (CannotForge blk)
, Show (ForgeStateInfo blk)
, Show (ForgeStateUpdateError blk)
, ShowProxy blk
, ShowProxy (ApplyTxErr blk)
, ShowProxy (GenTx blk)
, ShowProxy (Header blk)
, ShowProxy (BlockQuery blk)
, ShowProxy (TxId (GenTx blk))
) => RunNode blk