Safe Haskell | None |
---|---|
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)]
- 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
- 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
- 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
- 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 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 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)) → 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 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 {}
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)] 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 Source #
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 |
Instances
Headers
type CardanoHeader c = Header (CardanoBlock c) Source #
The Cardano header.
data family Header blk Source #
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.
data family GenTx blk Source #
Generalized transaction
The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.
Instances
data HardForkApplyTxErr (xs ∷ [Type]) where Source #
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 |
Instances
A generalized transaction, GenTx
, identifier.
Instances
type Rep (TxId (GenTx (HardForkBlock xs))) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.1.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs)))) | |
newtype TxId (GenTx (HardForkBlock xs)) | |
data TxId (GenTx ByronBlock) | |
Defined in Ouroboros.Consensus.Byron.Ledger.Mempool data TxId (GenTx ByronBlock)
| |
newtype TxId (GenTx (ShelleyBlock proto era)) | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool |
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 Source #
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 |
Instances
OtherEnvelopeError
type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c) Source #
An error resulting from validating a CardanoHeader
.
data HardForkEnvelopeErr (xs ∷ [Type]) where Source #
Bundled Patterns
pattern OtherHeaderEnvelopeErrorAllegra ∷ OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AllegraEra c)) → CardanoOtherHeaderEnvelopeError c | |
pattern OtherHeaderEnvelopeErrorBabbage ∷ OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (BabbageEra 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 |
Instances
TipInfo
type CardanoTipInfo c = OneEraTipInfo (CardanoEras c) Source #
The TipInfo
of the Cardano chain.
data OneEraTipInfo (xs ∷ [Type]) where Source #
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 TipInfoMary ∷ TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) → CardanoTipInfo c | |
pattern TipInfoShelley ∷ TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) → CardanoTipInfo c |
Instances
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 ⇒ Show (OneEraTipInfo xs) | |
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 Source #
Different queries supported by the ledger, indexed by the result type.
Instances
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
Hashable2 Either | |
Defined in Data.Hashable.Class | |
MonadError e (Either e) | |
Defined in Control.Monad.Error.Class Methods throwError ∷ e → Either e a Source # catchError ∷ Either e a → (e → Either e a) → Either e a Source # | |
(Lift a, Lift b) ⇒ Lift (Either a b ∷ Type) | |
Monad (Either e) | Since: base-4.4.0.0 |
Functor (Either a) | Since: base-3.0 |
Applicative (Either e) | Since: base-3.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 # | |
Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Hashable a ⇒ Hashable1 (Either a) | |
Defined in Data.Hashable.Class | |
MonadFailure (Either a) | |
Defined in Basement.Monad Associated Types type Failure (Either a) | |
Generic1 (Either a ∷ Type → Type) | Since: base-4.6.0.0 |
MonadBaseControl (Either e) (Either e) | |
Defined in Control.Monad.Trans.Control Associated Types type StM (Either e) a | |
(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 | |
(Read a, Read b) ⇒ Read (Either a b) | Since: base-3.0 |
(Show a, Show b) ⇒ Show (Either a b) | Since: base-3.0 |
Generic (Either a b) | Since: base-4.6.0.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
(Structured a, Structured b) ⇒ Structured (Either a b) | |
Defined in Distribution.Utils.Structured | |
(Serialise a, Serialise b) ⇒ Serialise (Either a b) | |
Defined in Codec.Serialise.Class | |
(NoThunks a, NoThunks b) ⇒ NoThunks (Either a b) | |
(Hashable a, Hashable b) ⇒ Hashable (Either a b) | |
Defined in Data.Hashable.Class | |
(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 ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (Either a b) → Size encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [Either a b] → Size | |
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) ⇒ (∀ 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) ⇒ (∀ b0. m (Base (Either a b) b0) → Base (Either a b) (m b0)) → (∀ 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) ⇒ (∀ 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) ⇒ (∀ 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) ⇒ (∀ b0. Base (Either a b) (w b0) → w (Base (Either a b) b0)) → (∀ c. Base (Either a b) c → Base (Either a b) c) → (Base (Either a b) (w a0) → a0) → Either a b → a0 | |
(Ord a, Ord b) ⇒ Ord (Either a b) | |
Defined in PlutusTx.Ord | |
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) | |
MonoTraversable (Either a b) | |
Defined in Data.MonoTraversable | |
MonoFunctor (Either a b) | |
MonoPointed (Either a b) | |
Defined in Data.MonoTraversable | |
(a ~ a', b ~ b') ⇒ Each (Either a a') (Either b b') a b | |
Defined in Lens.Micro.Internal | |
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 Rep1 (Either a ∷ Type → Type) | |
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 Rep (Either a b) | |
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 Base (Either a b) | |
type Element (Either a b) | |
Defined in Data.MonoTraversable type Element (Either a b) = 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 Source #
Static configuration required for serialisation and deserialisation of types pertaining to this type of block.
Data family instead of type family to get better type inference.
Instances
BlockConfig
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
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 Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
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 Source #
Static configuration required to run the consensus protocol
Every method in the ConsensusProtocol
class takes the consensus
configuration as a parameter, so having this as a data family rather than a
type family resolves most ambiguity.
Defined out of the class so that protocols can define this type without having to define the entire protocol at the same time (or indeed in the same module).
Instances
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 Source #
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)) → 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 Source #
Ledger state associated with a block
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 Source #
Generic hard fork state
This is used both for the consensus state and the ledger state.
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 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
data Ticked (HardForkChainDepState xs) | |
type SListIN HardForkState | |
type Prod HardForkState | |
type AllN HardForkState (c ∷ Type → Constraint) | |
type CollapseTo HardForkState a | |
EraMismatch
data EraMismatch Source #
Extra info for errors caused by applying a block, header, transaction, or query from one era to a ledger from a different era.
Constructors
EraMismatch | |
Fields
|
Instances
Eq EraMismatch | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras Methods (==) ∷ EraMismatch → EraMismatch → Bool Source # (/=) ∷ EraMismatch → EraMismatch → Bool Source # | |
Show EraMismatch | |
Generic EraMismatch | |
type Rep EraMismatch | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras type Rep EraMismatch = D1 ('MetaData "EraMismatch" "Ouroboros.Consensus.HardFork.Combinator.AcrossEras" "ouroboros-consensus-0.1.0.0-inplace" 'False) (C1 ('MetaCons "EraMismatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "otherEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |