{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeFamilies #-}
module Ouroboros.Consensus.Node.ProtocolInfo (
NumCoreNodes (..)
, ProtocolClientInfo (..)
, ProtocolInfo (..)
, enumCoreNodes
) where
import Data.Word
import NoThunks.Class (NoThunks)
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Config
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.NodeId
newtype NumCoreNodes = NumCoreNodes Word64
deriving (Int -> NumCoreNodes -> ShowS
[NumCoreNodes] -> ShowS
NumCoreNodes -> String
(Int -> NumCoreNodes -> ShowS)
-> (NumCoreNodes -> String)
-> ([NumCoreNodes] -> ShowS)
-> Show NumCoreNodes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumCoreNodes -> ShowS
showsPrec :: Int -> NumCoreNodes -> ShowS
$cshow :: NumCoreNodes -> String
show :: NumCoreNodes -> String
$cshowList :: [NumCoreNodes] -> ShowS
showList :: [NumCoreNodes] -> ShowS
Show, Context -> NumCoreNodes -> IO (Maybe ThunkInfo)
Proxy NumCoreNodes -> String
(Context -> NumCoreNodes -> IO (Maybe ThunkInfo))
-> (Context -> NumCoreNodes -> IO (Maybe ThunkInfo))
-> (Proxy NumCoreNodes -> String)
-> NoThunks NumCoreNodes
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> NumCoreNodes -> IO (Maybe ThunkInfo)
noThunks :: Context -> NumCoreNodes -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> NumCoreNodes -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> NumCoreNodes -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy NumCoreNodes -> String
showTypeOf :: Proxy NumCoreNodes -> String
NoThunks)
enumCoreNodes :: NumCoreNodes -> [CoreNodeId]
enumCoreNodes :: NumCoreNodes -> [CoreNodeId]
enumCoreNodes (NumCoreNodes Word64
0) = []
enumCoreNodes (NumCoreNodes Word64
numNodes) =
[ Word64 -> CoreNodeId
CoreNodeId Word64
n | Word64
n <- [Word64
0 .. Word64
numNodes Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
1] ]
data ProtocolInfo b = ProtocolInfo {
forall b. ProtocolInfo b -> TopLevelConfig b
pInfoConfig :: TopLevelConfig b
, forall b. ProtocolInfo b -> ExtLedgerState b
pInfoInitLedger :: ExtLedgerState b
}
data ProtocolClientInfo b = ProtocolClientInfo {
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig :: CodecConfig b
}