Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Cardano.Block
Synopsis
- type CardanoEras c = ByronBlock ': CardanoShelleyEras c
- type CardanoShelleyEras c = '[ShelleyBlock (TPraos c) (ShelleyEra c), ShelleyBlock (TPraos c) (AllegraEra c), ShelleyBlock (TPraos c) (MaryEra c), ShelleyBlock (TPraos c) (AlonzoEra c), ShelleyBlock (Praos c) (BabbageEra c), ShelleyBlock (Praos c) (ConwayEra c)]
- module Ouroboros.Consensus.Shelley.Eras
- type CardanoBlock c = HardForkBlock (CardanoEras c)
- data HardForkBlock (xs :: [Type]) where
- pattern BlockAllegra :: ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c
- pattern BlockAlonzo :: ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c
- pattern BlockByron :: ByronBlock -> CardanoBlock c
- pattern BlockMary :: ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c
- pattern BlockShelley :: ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c
- pattern BlockBabbage :: ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c
- pattern BlockConway :: ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c
- type CardanoHeader c = Header (CardanoBlock c)
- data family Header blk
- type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c)
- type CardanoGenTx c = GenTx (CardanoBlock c)
- type CardanoGenTxId c = GenTxId (CardanoBlock c)
- data family GenTx blk
- data HardForkApplyTxErr (xs :: [Type]) where
- pattern ApplyTxErrAllegra :: ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoApplyTxErr c
- pattern ApplyTxErrAlonzo :: ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoApplyTxErr c
- pattern ApplyTxErrByron :: ApplyTxErr ByronBlock -> CardanoApplyTxErr c
- pattern ApplyTxErrMary :: ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoApplyTxErr c
- pattern ApplyTxErrShelley :: ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoApplyTxErr c
- pattern ApplyTxErrWrongEra :: EraMismatch -> CardanoApplyTxErr c
- pattern ApplyTxErrBabbage :: ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoApplyTxErr c
- pattern ApplyTxErrConway :: ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoApplyTxErr c
- data family TxId tx
- type CardanoLedgerError c = HardForkLedgerError (CardanoEras c)
- data HardForkLedgerError (xs :: [Type]) where
- pattern LedgerErrorAllegra :: LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoLedgerError c
- pattern LedgerErrorAlonzo :: LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoLedgerError c
- pattern LedgerErrorByron :: LedgerError ByronBlock -> CardanoLedgerError c
- pattern LedgerErrorMary :: LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoLedgerError c
- pattern LedgerErrorShelley :: LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoLedgerError c
- pattern LedgerErrorWrongEra :: EraMismatch -> CardanoLedgerError c
- pattern LedgerErrorBabbage :: LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoLedgerError c
- pattern LedgerErrorConway :: LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerError c
- type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c)
- data HardForkEnvelopeErr (xs :: [Type]) where
- pattern OtherHeaderEnvelopeErrorAllegra :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorBabbage :: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorConway :: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorAlonzo :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorByron :: OtherHeaderEnvelopeError ByronBlock -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorMary :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorShelley :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoOtherHeaderEnvelopeError c
- pattern OtherHeaderEnvelopeErrorWrongEra :: EraMismatch -> CardanoOtherHeaderEnvelopeError c
- type CardanoTipInfo c = OneEraTipInfo (CardanoEras c)
- data OneEraTipInfo (xs :: [Type]) where
- pattern TipInfoAllegra :: TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoTipInfo c
- pattern TipInfoAlonzo :: TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoTipInfo c
- pattern TipInfoByron :: TipInfo ByronBlock -> CardanoTipInfo c
- pattern TipInfoBabbage :: TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoTipInfo c
- pattern TipInfoConway :: TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoTipInfo c
- pattern TipInfoMary :: TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoTipInfo c
- pattern TipInfoShelley :: TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoTipInfo c
- data family BlockQuery blk :: Type -> Type
- type CardanoQuery c = BlockQuery (CardanoBlock c)
- type CardanoQueryResult c = HardForkQueryResult (CardanoEras c)
- data Either a b where
- pattern QueryResultSuccess :: result -> CardanoQueryResult c result
- pattern QueryResultEraMismatch :: EraMismatch -> CardanoQueryResult c result
- type CardanoCodecConfig c = CodecConfig (CardanoBlock c)
- data family CodecConfig blk
- data family BlockConfig blk
- type CardanoBlockConfig c = BlockConfig (CardanoBlock c)
- type CardanoStorageConfig c = StorageConfig (CardanoBlock c)
- data family StorageConfig blk
- type CardanoConsensusConfig c = ConsensusConfig (HardForkProtocol (CardanoEras c))
- data family ConsensusConfig p
- type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c)
- data HardForkLedgerConfig (xs :: [Type]) where
- pattern CardanoLedgerConfig :: PartialLedgerConfig ByronBlock -> PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerConfig c
- type CardanoLedgerState c = LedgerState (CardanoBlock c)
- data family LedgerState blk
- type CardanoChainDepState c = HardForkChainDepState (CardanoEras c)
- data HardForkState (f :: Type -> Type) (xs :: [Type]) where
- pattern ChainDepStateAllegra :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c))) -> CardanoChainDepState c
- pattern ChainDepStateAlonzo :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))) -> CardanoChainDepState c
- pattern ChainDepStateBabbage :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c))) -> CardanoChainDepState c
- pattern ChainDepStateConway :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c))) -> CardanoChainDepState c
- pattern ChainDepStateByron :: ChainDepState (BlockProtocol ByronBlock) -> CardanoChainDepState c
- pattern ChainDepStateMary :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c))) -> CardanoChainDepState c
- pattern ChainDepStateShelley :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))) -> CardanoChainDepState c
- data EraMismatch = EraMismatch {
- ledgerEraName :: !Text
- otherEraName :: !Text
Eras
type CardanoEras c = ByronBlock ': CardanoShelleyEras c Source #
The eras in the Cardano blockchain.
We parameterise over the crypto used in the post-Byron eras: c
.
TODO: parameterise ByronBlock over crypto too
type CardanoShelleyEras c = '[ShelleyBlock (TPraos c) (ShelleyEra c), ShelleyBlock (TPraos c) (AllegraEra c), ShelleyBlock (TPraos c) (MaryEra c), ShelleyBlock (TPraos c) (AlonzoEra c), ShelleyBlock (Praos c) (BabbageEra c), ShelleyBlock (Praos c) (ConwayEra c)] Source #
Block
type CardanoBlock c = HardForkBlock (CardanoEras c) Source #
The Cardano block.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors BlockByron
and BlockShelley
.
f :: CardanoBlock c -> _ f (BlockByron b) = _ f (BlockShelley s) = _ f (BlockAllegra a) = _ f (BlockMary m) = _ f (BlockAlonzo m) = _
data HardForkBlock (xs :: [Type]) where #
Bundled Patterns
pattern BlockAllegra :: ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c | |
pattern BlockAlonzo :: ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c | |
pattern BlockByron :: ByronBlock -> CardanoBlock c | |
pattern BlockMary :: ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c | |
pattern BlockShelley :: ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c | |
pattern BlockBabbage :: ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c | |
pattern BlockConway :: ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c |
Instances
Headers
type CardanoHeader c = Header (CardanoBlock c) Source #
The Cardano header.
Instances
Generalised transactions
type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c) Source #
An error resulting from applying a CardanoGenTx
to the ledger.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors ApplyTxByronErr
, ApplyTxErrShelley
, and
ApplyTxErrWrongEra
.
toText :: CardanoApplyTxErr c -> Text toText (ApplyTxErrByron b) = byronApplyTxErrToText b toText (ApplyTxErrShelley s) = shelleyApplyTxErrToText s toText (ApplyTxErrAllegra a) = allegraApplyTxErrToText a toText (ApplyTxErrMary m) = maryApplyTxErrToText m toText (ApplyTxErrWrongEra eraMismatch) = "Transaction from the " <> otherEraName eraMismatch <> " era applied to a ledger from the " <> ledgerEraName eraMismatch <> " era"
type CardanoGenTx c = GenTx (CardanoBlock c) Source #
The Cardano transaction.
type CardanoGenTxId c = GenTxId (CardanoBlock c) Source #
The ID of a Cardano transaction.
Instances
data HardForkApplyTxErr (xs :: [Type]) where #
Bundled Patterns
pattern ApplyTxErrAllegra :: ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoApplyTxErr c | |
pattern ApplyTxErrAlonzo :: ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoApplyTxErr c | |
pattern ApplyTxErrByron :: ApplyTxErr ByronBlock -> CardanoApplyTxErr c | |
pattern ApplyTxErrMary :: ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoApplyTxErr c | |
pattern ApplyTxErrShelley :: ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoApplyTxErr c | |
pattern ApplyTxErrWrongEra :: EraMismatch -> CardanoApplyTxErr c | |
pattern ApplyTxErrBabbage :: ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoApplyTxErr c | |
pattern ApplyTxErrConway :: ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoApplyTxErr c |
Instances
Instances
LedgerError
type CardanoLedgerError c = HardForkLedgerError (CardanoEras c) Source #
An error resulting from applying a CardanoBlock
to the ledger.
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors LedgerErrorByron
, LedgerErrorShelley
, and
LedgerErrorWrongEra
.
toText :: CardanoLedgerError c -> Text toText (LedgerErrorByron b) = byronLedgerErrorToText b toText (LedgerErrorShelley s) = shelleyLedgerErrorToText s toText (LedgerErrorAllegra a) = allegraLedgerErrorToText a toText (LedgerErrorMary m) = maryLedgerErrorToText m toText (LedgerErrorWrongEra eraMismatch) = "Block from the " <> otherEraName eraMismatch <> " era applied to a ledger from the " <> ledgerEraName eraMismatch <> " era"
data HardForkLedgerError (xs :: [Type]) where #
Bundled Patterns
pattern LedgerErrorAllegra :: LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoLedgerError c | |
pattern LedgerErrorAlonzo :: LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoLedgerError c | |
pattern LedgerErrorByron :: LedgerError ByronBlock -> CardanoLedgerError c | |
pattern LedgerErrorMary :: LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoLedgerError c | |
pattern LedgerErrorShelley :: LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoLedgerError c | |
pattern LedgerErrorWrongEra :: EraMismatch -> CardanoLedgerError c | |
pattern LedgerErrorBabbage :: LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoLedgerError c | |
pattern LedgerErrorConway :: LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerError c |
Instances
OtherEnvelopeError
type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c) Source #
An error resulting from validating a CardanoHeader
.
data HardForkEnvelopeErr (xs :: [Type]) where #
Bundled Patterns
Instances
TipInfo
type CardanoTipInfo c = OneEraTipInfo (CardanoEras c) Source #
The TipInfo
of the Cardano chain.
data OneEraTipInfo (xs :: [Type]) where #
Bundled Patterns
pattern TipInfoAllegra :: TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoTipInfo c | |
pattern TipInfoAlonzo :: TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoTipInfo c | |
pattern TipInfoByron :: TipInfo ByronBlock -> CardanoTipInfo c | |
pattern TipInfoBabbage :: TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoTipInfo c | |
pattern TipInfoConway :: TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoTipInfo c | |
pattern TipInfoMary :: TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoTipInfo c | |
pattern TipInfoShelley :: TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoTipInfo c |
Instances
CanHardFork xs => Show (OneEraTipInfo xs) | |
CanHardFork xs => Eq (OneEraTipInfo xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) :: OneEraTipInfo xs -> OneEraTipInfo xs -> Bool Source # (/=) :: OneEraTipInfo xs -> OneEraTipInfo xs -> Bool Source # | |
CanHardFork xs => NoThunks (OneEraTipInfo xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods noThunks :: Context -> OneEraTipInfo xs -> IO (Maybe ThunkInfo) wNoThunks :: Context -> OneEraTipInfo xs -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (OneEraTipInfo xs) -> String |
Query
data family BlockQuery blk :: Type -> Type #
Instances
SerialiseResult ByronBlock (BlockQuery ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Node.Serialisation Methods encodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> result -> Encoding decodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> forall s. Decoder s result | |
SerialiseNodeToClient ByronBlock (SomeSecond BlockQuery ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Node.Serialisation Methods encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> SomeSecond BlockQuery ByronBlock -> Encoding decodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> forall s. Decoder s (SomeSecond BlockQuery ByronBlock) | |
Inject (SomeSecond BlockQuery) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> SomeSecond BlockQuery x -> SomeSecond BlockQuery (HardForkBlock xs) | |
SameDepIndex (BlockQuery ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Methods sameDepIndex :: BlockQuery ByronBlock a -> BlockQuery ByronBlock b -> Maybe (a :~: b) | |
SameDepIndex (BlockQuery (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods sameDepIndex :: BlockQuery (ShelleyBlock proto era) a -> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b) | |
ShowQuery (BlockQuery ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Methods showResult :: BlockQuery ByronBlock result -> result -> String | |
ShelleyCompatible proto era => ShowQuery (BlockQuery (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods showResult :: BlockQuery (ShelleyBlock proto era) result -> result -> String | |
Show (BlockQuery ByronBlock result) Source # | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Methods showsPrec :: Int -> BlockQuery ByronBlock result -> ShowS Source # show :: BlockQuery ByronBlock result -> String Source # showList :: [BlockQuery ByronBlock result] -> ShowS Source # | |
Show (BlockQuery (ShelleyBlock proto era) result) Source # | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods showsPrec :: Int -> BlockQuery (ShelleyBlock proto era) result -> ShowS Source # show :: BlockQuery (ShelleyBlock proto era) result -> String Source # showList :: [BlockQuery (ShelleyBlock proto era) result] -> ShowS Source # | |
(forall result. Show (BlockQuery blk result)) => Show (SomeSecond BlockQuery blk) | |
Defined in Ouroboros.Consensus.Ledger.Query | |
Eq (BlockQuery ByronBlock result) Source # | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Methods (==) :: BlockQuery ByronBlock result -> BlockQuery ByronBlock result -> Bool Source # (/=) :: BlockQuery ByronBlock result -> BlockQuery ByronBlock result -> Bool Source # | |
Eq (BlockQuery (ShelleyBlock proto era) result) Source # | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods (==) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source # (/=) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source # | |
SameDepIndex (BlockQuery blk) => Eq (SomeSecond BlockQuery blk) | |
Defined in Ouroboros.Consensus.Ledger.Query Methods (==) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source # (/=) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source # | |
ShelleyCompatible proto era => SerialiseResult (ShelleyBlock proto era) (BlockQuery (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Node.Serialisation Methods encodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding decodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result | |
ShowProxy (BlockQuery ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger Methods showProxy :: Proxy (BlockQuery ByronBlock) -> String | |
(Typeable era, Typeable proto) => ShowProxy (BlockQuery (ShelleyBlock proto era) :: Type -> Type) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query Methods showProxy :: Proxy (BlockQuery (ShelleyBlock proto era)) -> String | |
ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (SomeSecond BlockQuery (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Node.Serialisation Methods encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> SomeSecond BlockQuery (ShelleyBlock proto era) -> Encoding decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)) | |
data BlockQuery ByronBlock a Source # | |
Defined in Ouroboros.Consensus.Byron.Ledger.Ledger | |
data BlockQuery (HardForkBlock xs) a | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query data BlockQuery (HardForkBlock xs) a where
| |
data BlockQuery (ShelleyBlock proto era) a Source # | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Query data BlockQuery (ShelleyBlock proto era) a where
|
type CardanoQuery c = BlockQuery (CardanoBlock c) Source #
The Query
of Cardano chain.
type CardanoQueryResult c = HardForkQueryResult (CardanoEras c) Source #
The result of a CardanoQuery
Thanks to the pattern synonyms, you can treat this as a sum type with
constructors QueryResultSuccess
and QueryResultEraMismatch
.
data Either a b where Source #
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is
either correct or an error; by convention, the Left
constructor is
used to hold an error value and the Right
constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but
will apply the supplied function to values contained in a Right
:
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
fmap (*2) s
Left "foo">>>
fmap (*2) n
Right 6
The Monad
instance for Either
allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int
from a Char
, or fail.
>>>
import Data.Char ( digitToInt, isDigit )
>>>
:{
let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>
:}
The following should work, since both '1'
and '2'
can be
parsed as Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 3
But the following should fail overall, since the first operation where
we attempt to parse 'm'
as an Int
will fail:
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Left "parse error"
Bundled Patterns
pattern QueryResultSuccess :: result -> CardanoQueryResult c result | |
pattern QueryResultEraMismatch :: EraMismatch -> CardanoQueryResult c result | A query from a different era than the ledger's era was sent. |
Instances
FromJSON2 Either | |
Defined in Data.Aeson.Types.FromJSON Methods liftParseJSON2 :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe b -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Either a b) liftParseJSONList2 :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe b -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Either a b] liftOmittedField2 :: Maybe a -> Maybe b -> Maybe (Either a b) | |
ToJSON2 Either | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> (b -> Bool) -> (b -> Value) -> ([b] -> Value) -> Either a b -> Value liftToJSONList2 :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> (b -> Bool) -> (b -> Value) -> ([b] -> Value) -> [Either a b] -> Value liftToEncoding2 :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> (b -> Bool) -> (b -> Encoding) -> ([b] -> Encoding) -> Either a b -> Encoding liftToEncodingList2 :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> (b -> Bool) -> (b -> Encoding) -> ([b] -> Encoding) -> [Either a b] -> Encoding liftOmitField2 :: (a -> Bool) -> (b -> Bool) -> Either a b -> Bool | |
Bifunctor Either | Since: base-4.8.0.0 |
Eq2 Either | Since: base-4.9.0.0 |
Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) Source # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] Source # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) Source # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] Source # | |
Show2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
NFData2 Either | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 Either | |
Defined in Data.Hashable.Class | |
Generic1 (Either a :: Type -> Type) | |
MonadError e (Either e) | |
Defined in Control.Monad.Error.Class | |
(Lift a, Lift b) => Lift (Either a b :: Type) | |
FromJSON a => FromJSON1 (Either a) | |
Defined in Data.Aeson.Types.FromJSON Methods liftParseJSON :: Maybe a0 -> (Value -> Parser a0) -> (Value -> Parser [a0]) -> Value -> Parser (Either a a0) liftParseJSONList :: Maybe a0 -> (Value -> Parser a0) -> (Value -> Parser [a0]) -> Value -> Parser [Either a a0] liftOmittedField :: Maybe a0 -> Maybe (Either a a0) | |
ToJSON a => ToJSON1 (Either a) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Bool) -> (a0 -> Value) -> ([a0] -> Value) -> Either a a0 -> Value liftToJSONList :: (a0 -> Bool) -> (a0 -> Value) -> ([a0] -> Value) -> [Either a a0] -> Value liftToEncoding :: (a0 -> Bool) -> (a0 -> Encoding) -> ([a0] -> Encoding) -> Either a a0 -> Encoding liftToEncodingList :: (a0 -> Bool) -> (a0 -> Encoding) -> ([a0] -> Encoding) -> [Either a a0] -> Encoding liftOmitField :: (a0 -> Bool) -> Either a a0 -> Bool | |
MonadFix (Either e) | Since: base-4.3.0.0 |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m Source # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source # foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source # foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source # foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source # foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source # foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source # foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source # foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source # toList :: Either a a0 -> [a0] Source # null :: Either a a0 -> Bool Source # length :: Either a a0 -> Int Source # elem :: Eq a0 => a0 -> Either a a0 -> Bool Source # maximum :: Ord a0 => Either a a0 -> a0 Source # minimum :: Ord a0 => Either a a0 -> a0 Source # | |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) Source # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] Source # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) Source # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] Source # | |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable Methods traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source # sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source # mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source # sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source # | |
Applicative (Either e) | Since: base-3.0 |
Defined in Data.Either | |
Functor (Either a) | Since: base-3.0 |
Monad (Either e) | Since: base-4.4.0.0 |
MonadFailure (Either a) | |
Defined in Basement.Monad Associated Types type Failure (Either a) | |
NFData a => NFData1 (Either a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Either a) | |
Defined in Data.Hashable.Class | |
MonadBaseControl (Either e) (Either e) | |
Defined in Control.Monad.Trans.Control Associated Types type StM (Either e) a | |
(Structured a, Structured b) => Structured (Either a b) | |
Defined in Distribution.Utils.Structured | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
Defined in Data.Aeson.Types.FromJSON Methods parseJSON :: Value -> Parser (Either a b) parseJSONList :: Value -> Parser [Either a b] omittedField :: Maybe (Either a b) | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
Defined in Data.Aeson.Types.ToJSON Methods toEncoding :: Either a b -> Encoding toJSONList :: [Either a b] -> Value toEncodingList :: [Either a b] -> Encoding | |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) Source # toConstr :: Either a b -> Constr Source # dataTypeOf :: Either a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source # | |
Semigroup (Either a b) | Since: base-4.9.0.0 |
Generic (Either a b) | |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
(FromCBOR a, FromCBOR b) => FromCBOR (Either a b) | |
(ToCBOR a, ToCBOR b) => ToCBOR (Either a b) | |
Defined in Cardano.Binary.ToCBOR Methods toCBOR :: Either a b -> Encoding encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Either a b) -> Size encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Either a b] -> Size | |
(DecCBOR a, DecCBOR b) => DecCBOR (Either a b) | |
(EncCBOR a, EncCBOR b) => EncCBOR (Either a b) | |
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: Either a b -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Either a b) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Either a b] -> Size | |
(NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
Defined in Data.Either Methods compare :: Either a b -> Either a b -> Ordering Source # (<) :: Either a b -> Either a b -> Bool Source # (<=) :: Either a b -> Either a b -> Bool Source # (>) :: Either a b -> Either a b -> Bool Source # (>=) :: Either a b -> Either a b -> Bool Source # | |
(Hashable a, Hashable b) => Hashable (Either a b) | |
Defined in Data.Hashable.Class | |
MonoFoldable (Either a b) | |
Defined in Data.MonoTraversable Methods ofoldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m ofoldr :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0 ofoldl' :: (a0 -> Element (Either a b) -> a0) -> a0 -> Either a b -> a0 otoList :: Either a b -> [Element (Either a b)] oall :: (Element (Either a b) -> Bool) -> Either a b -> Bool oany :: (Element (Either a b) -> Bool) -> Either a b -> Bool olength64 :: Either a b -> Int64 ocompareLength :: Integral i => Either a b -> i -> Ordering otraverse_ :: Applicative f => (Element (Either a b) -> f b0) -> Either a b -> f () ofor_ :: Applicative f => Either a b -> (Element (Either a b) -> f b0) -> f () omapM_ :: Applicative m => (Element (Either a b) -> m ()) -> Either a b -> m () oforM_ :: Applicative m => Either a b -> (Element (Either a b) -> m ()) -> m () ofoldlM :: Monad m => (a0 -> Element (Either a b) -> m a0) -> a0 -> Either a b -> m a0 ofoldMap1Ex :: Semigroup m => (Element (Either a b) -> m) -> Either a b -> m ofoldr1Ex :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) ofoldl1Ex' :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) headEx :: Either a b -> Element (Either a b) lastEx :: Either a b -> Element (Either a b) unsafeHead :: Either a b -> Element (Either a b) unsafeLast :: Either a b -> Element (Either a b) maximumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) minimumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) | |
MonoFunctor (Either a b) | |
MonoPointed (Either a b) | |
Defined in Data.MonoTraversable | |
MonoTraversable (Either a b) | |
Defined in Data.MonoTraversable | |
(NoThunks a, NoThunks b) => NoThunks (Either a b) | |
(Eq a, Eq b) => Eq (Either a b) | |
Defined in PlutusTx.Eq | |
(Ord a, Ord b) => Ord (Either a b) | |
Corecursive (Either a b) | |
Defined in Data.Functor.Foldable Methods embed :: Base (Either a b) (Either a b) -> Either a b ana :: (a0 -> Base (Either a b) a0) -> a0 -> Either a b apo :: (a0 -> Base (Either a b) (Either (Either a b) a0)) -> a0 -> Either a b postpro :: Recursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (a0 -> Base (Either a b) a0) -> a0 -> Either a b gpostpro :: (Recursive (Either a b), Monad m) => (forall b0. m (Base (Either a b) b0) -> Base (Either a b) (m b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (a0 -> Base (Either a b) (m a0)) -> a0 -> Either a b | |
Recursive (Either a b) | |
Defined in Data.Functor.Foldable Methods project :: Either a b -> Base (Either a b) (Either a b) cata :: (Base (Either a b) a0 -> a0) -> Either a b -> a0 para :: (Base (Either a b) (Either a b, a0) -> a0) -> Either a b -> a0 gpara :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (Base (Either a b) (EnvT (Either a b) w a0) -> a0) -> Either a b -> a0 prepro :: Corecursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (Base (Either a b) a0 -> a0) -> Either a b -> a0 gprepro :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (Base (Either a b) (w a0) -> a0) -> Either a b -> a0 | |
(Serialise a, Serialise b) => Serialise (Either a b) | |
Defined in Codec.Serialise.Class Methods encode :: Either a b -> Encoding decode :: Decoder s (Either a b) encodeList :: [Either a b] -> Encoding decodeList :: Decoder s [Either a b] | |
(ToExpr a, ToExpr b) => ToExpr (Either a b) | |
Defined in Data.TreeDiff.Class | |
(a ~ a', b ~ b') => Each (Either a a') (Either b b') a b | |
Defined in Lens.Micro.Internal | |
type Rep1 (Either a :: Type -> Type) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
type Failure (Either a) | |
Defined in Basement.Monad type Failure (Either a) = a | |
type StM (Either e) a | |
Defined in Control.Monad.Trans.Control type StM (Either e) a = a | |
type Rep (Either a b) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (Either a b) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))) | |
type Element (Either a b) | |
Defined in Data.MonoTraversable type Element (Either a b) = b | |
type Base (Either a b) | |
CodecConfig
type CardanoCodecConfig c = CodecConfig (CardanoBlock c) Source #
The CodecConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... CodecConfig
s.
data family CodecConfig blk #
Instances
BlockConfig
data family BlockConfig blk #
Instances
type CardanoBlockConfig c = BlockConfig (CardanoBlock c) Source #
The BlockConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... BlockConfig
s.
StorageConfig
type CardanoStorageConfig c = StorageConfig (CardanoBlock c) Source #
The StorageConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of
the Byron, Shelley, ... StorageConfig
s.
data family StorageConfig blk #
Instances
ConsensusConfig
type CardanoConsensusConfig c = ConsensusConfig (HardForkProtocol (CardanoEras c)) Source #
The ConsensusConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of the
Byron, Shelley, ... PartialConsensusConfig
s.
NOTE: not ConsensusConfig
, but PartialConsensusConfig
.
data family ConsensusConfig p #
Instances
Generic (ConsensusConfig (HardForkProtocol xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods from :: ConsensusConfig (HardForkProtocol xs) -> Rep (ConsensusConfig (HardForkProtocol xs)) x Source # to :: Rep (ConsensusConfig (HardForkProtocol xs)) x -> ConsensusConfig (HardForkProtocol xs) Source # | |
Generic (ConsensusConfig (PBft c)) | |
Defined in Ouroboros.Consensus.Protocol.PBFT Methods from :: ConsensusConfig (PBft c) -> Rep (ConsensusConfig (PBft c)) x Source # to :: Rep (ConsensusConfig (PBft c)) x -> ConsensusConfig (PBft c) Source # | |
Generic (ConsensusConfig (Praos c)) | |
Defined in Ouroboros.Consensus.Protocol.Praos Methods from :: ConsensusConfig (Praos c) -> Rep (ConsensusConfig (Praos c)) x Source # to :: Rep (ConsensusConfig (Praos c)) x -> ConsensusConfig (Praos c) Source # | |
Generic (ConsensusConfig (TPraos c)) | |
Defined in Ouroboros.Consensus.Protocol.TPraos Methods from :: ConsensusConfig (TPraos c) -> Rep (ConsensusConfig (TPraos c)) x Source # to :: Rep (ConsensusConfig (TPraos c)) x -> ConsensusConfig (TPraos c) Source # | |
CanHardFork xs => NoThunks (ConsensusConfig (HardForkProtocol xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks :: Context -> ConsensusConfig (HardForkProtocol xs) -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ConsensusConfig (HardForkProtocol xs) -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ConsensusConfig (HardForkProtocol xs)) -> String | |
NoThunks (ConsensusConfig (PBft c)) | |
Defined in Ouroboros.Consensus.Protocol.PBFT Methods noThunks :: Context -> ConsensusConfig (PBft c) -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ConsensusConfig (PBft c) -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ConsensusConfig (PBft c)) -> String | |
PraosCrypto c => NoThunks (ConsensusConfig (Praos c)) | |
Defined in Ouroboros.Consensus.Protocol.Praos Methods noThunks :: Context -> ConsensusConfig (Praos c) -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ConsensusConfig (Praos c) -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ConsensusConfig (Praos c)) -> String | |
PraosCrypto c => NoThunks (ConsensusConfig (TPraos c)) | |
Defined in Ouroboros.Consensus.Protocol.TPraos Methods noThunks :: Context -> ConsensusConfig (TPraos c) -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ConsensusConfig (TPraos c) -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ConsensusConfig (TPraos c)) -> String | |
type Rep (ConsensusConfig (HardForkProtocol xs)) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type Rep (ConsensusConfig (HardForkProtocol xs)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkConsensusConfigK") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "hardForkConsensusConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkConsensusConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraConsensusConfig xs))))) | |
type Rep (ConsensusConfig (PBft c)) | |
Defined in Ouroboros.Consensus.Protocol.PBFT type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams))) | |
type Rep (ConsensusConfig (Praos c)) | |
Defined in Ouroboros.Consensus.Protocol.Praos type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.6.0.0-9L9Rwb3KvaS6sYVJ3OHbE2" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: S1 ('MetaSel ('Just "praosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException))))) | |
type Rep (ConsensusConfig (TPraos c)) | |
Defined in Ouroboros.Consensus.Protocol.TPraos type Rep (ConsensusConfig (TPraos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.TPraos" "ouroboros-consensus-protocol-0.6.0.0-9L9Rwb3KvaS6sYVJ3OHbE2" 'False) (C1 ('MetaCons "TPraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tpraosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TPraosParams) :*: S1 ('MetaSel ('Just "tpraosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException))))) | |
data ConsensusConfig (HardForkProtocol xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics data ConsensusConfig (HardForkProtocol xs) = HardForkConsensusConfig {
| |
newtype ConsensusConfig (PBft c) | |
Defined in Ouroboros.Consensus.Protocol.PBFT | |
data ConsensusConfig (Praos c) | |
Defined in Ouroboros.Consensus.Protocol.Praos data ConsensusConfig (Praos c) = PraosConfig {
| |
data ConsensusConfig (TPraos c) | |
Defined in Ouroboros.Consensus.Protocol.TPraos data ConsensusConfig (TPraos c) = TPraosConfig {
|
LedgerConfig
type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c) Source #
The LedgerConfig
for CardanoBlock
.
Thanks to the pattern synonyms, you can treat this as the product of the
Byron, Shelley, ... PartialLedgerConfig
s.
NOTE: not LedgerConfig
, but PartialLedgerConfig
.
data HardForkLedgerConfig (xs :: [Type]) where #
Bundled Patterns
pattern CardanoLedgerConfig :: PartialLedgerConfig ByronBlock -> PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerConfig c |
Instances
LedgerState
type CardanoLedgerState c = LedgerState (CardanoBlock c) Source #
The LedgerState
for CardanoBlock
.
NOTE: the CardanoLedgerState
contains more than just the current era's
LedgerState
. We don't give access to those internal details through the
pattern synonyms. This is also the reason the pattern synonyms are not
bidirectional.
data family LedgerState blk #
Instances
ChainDepState
type CardanoChainDepState c = HardForkChainDepState (CardanoEras c) Source #
The ChainDepState
for CardanoBlock
.
NOTE: the CardanoChainDepState
contains more than just the current era's
ChainDepState
. We don't give access to those internal details through the
pattern synonyms. This is also the reason the pattern synonyms are not
bidirectional.
data HardForkState (f :: Type -> Type) (xs :: [Type]) where #
Bundled Patterns
pattern ChainDepStateAllegra :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c))) -> CardanoChainDepState c | |
pattern ChainDepStateAlonzo :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))) -> CardanoChainDepState c | |
pattern ChainDepStateBabbage :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c))) -> CardanoChainDepState c | |
pattern ChainDepStateConway :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c))) -> CardanoChainDepState c | |
pattern ChainDepStateByron :: ChainDepState (BlockProtocol ByronBlock) -> CardanoChainDepState c | |
pattern ChainDepStateMary :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c))) -> CardanoChainDepState c | |
pattern ChainDepStateShelley :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))) -> CardanoChainDepState c |
Instances
type Prod HardForkState | |
type SListIN HardForkState | |
type CollapseTo HardForkState a | |
Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances type CollapseTo HardForkState a = a | |
type AllN HardForkState (c :: Type -> Constraint) | |
data Ticked (HardForkChainDepState xs) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol data Ticked (HardForkChainDepState xs) = TickedHardForkChainDepState {
|
EraMismatch
data EraMismatch #
Constructors
EraMismatch | |
Fields
|
Instances
Generic EraMismatch | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods from :: EraMismatch -> Rep EraMismatch x Source # to :: Rep EraMismatch x -> EraMismatch Source # | |
Show EraMismatch | |
Eq EraMismatch | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) :: EraMismatch -> EraMismatch -> Bool Source # (/=) :: EraMismatch -> EraMismatch -> Bool Source # | |
type Rep EraMismatch | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras type Rep EraMismatch = D1 ('MetaData "EraMismatch" "Ouroboros.Consensus.HardFork.Combinator.AcrossEras" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "EraMismatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "otherEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |