Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data family BlockConfig blk ∷ Type
- data family BlockQuery blk ∷ Type → Type
- data family CodecConfig blk ∷ Type
- data family ConsensusConfig p ∷ Type
- data Either a b where
- pattern DegenQueryResult ∷ result → HardForkQueryResult '[b] result
- data family GenTx blk ∷ Type
- data HardForkApplyTxErr xs where
- pattern DegenApplyTxErr ∷ ∀ b. NoHardForks b ⇒ ApplyTxErr b → HardForkApplyTxErr '[b]
- data HardForkBlock xs where
- pattern DegenBlock ∷ ∀ b. NoHardForks b ⇒ b → HardForkBlock '[b]
- data HardForkEnvelopeErr xs where
- pattern DegenOtherHeaderEnvelopeError ∷ ∀ b. NoHardForks b ⇒ OtherHeaderEnvelopeError b → HardForkEnvelopeErr '[b]
- data HardForkLedgerConfig xs where
- pattern DegenLedgerConfig ∷ PartialLedgerConfig b → HardForkLedgerConfig '[b]
- data HardForkLedgerError xs where
- pattern DegenLedgerError ∷ ∀ b. NoHardForks b ⇒ LedgerError b → HardForkLedgerError '[b]
- data family Header blk ∷ Type
- data family LedgerState blk ∷ Type
- data OneEraTipInfo xs where
- pattern DegenTipInfo ∷ ∀ b. NoHardForks b ⇒ TipInfo b → OneEraTipInfo '[b]
- data TopLevelConfig blk where
- pattern DegenTopLevelConfig ∷ NoHardForks b ⇒ TopLevelConfig b → TopLevelConfig (HardForkBlock '[b])
- data family TxId tx ∷ Type
Pattern synonyms
data family BlockConfig blk ∷ Type Source #
Static configuration required to work with this type of blocks
Instances
data family BlockQuery blk ∷ Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
data family CodecConfig blk ∷ Type 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
data family ConsensusConfig p ∷ Type 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
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"
pattern DegenQueryResult ∷ result → HardForkQueryResult '[b] result |
Instances
data family GenTx blk ∷ Type 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 where Source #
pattern DegenApplyTxErr ∷ ∀ b. NoHardForks b ⇒ ApplyTxErr b → HardForkApplyTxErr '[b] |
Instances
data HardForkBlock xs where Source #
pattern DegenBlock ∷ ∀ b. NoHardForks b ⇒ b → HardForkBlock '[b] |
Instances
data HardForkEnvelopeErr xs where Source #
pattern DegenOtherHeaderEnvelopeError ∷ ∀ b. NoHardForks b ⇒ OtherHeaderEnvelopeError b → HardForkEnvelopeErr '[b] |
Instances
data HardForkLedgerConfig xs where Source #
pattern DegenLedgerConfig ∷ PartialLedgerConfig b → HardForkLedgerConfig '[b] |
Instances
Generic (HardForkLedgerConfig xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type Rep (HardForkLedgerConfig xs) ∷ Type → Type # from ∷ HardForkLedgerConfig xs → Rep (HardForkLedgerConfig xs) x # to ∷ Rep (HardForkLedgerConfig xs) x → HardForkLedgerConfig xs # | |
CanHardFork xs ⇒ NoThunks (HardForkLedgerConfig xs) Source # | |
type Rep (HardForkLedgerConfig xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics type Rep (HardForkLedgerConfig xs) = D1 ('MetaData "HardForkLedgerConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.21.0.0-inplace" 'False) (C1 ('MetaCons "HardForkLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkLedgerConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkLedgerConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraLedgerConfig xs)))) |
data HardForkLedgerError xs where Source #
pattern DegenLedgerError ∷ ∀ b. NoHardForks b ⇒ LedgerError b → HardForkLedgerError '[b] |
Instances
data family Header blk ∷ Type Source #
Instances
data family LedgerState blk ∷ Type Source #
Ledger state associated with a block
This is the Consensus notion of a ledger state. Each block type is
associated with one of the Ledger types for the ledger state. Virtually
every concept in this codebase revolves around this type, or the referenced
blk
. Whenever we use the type variable l
, we intend to denote that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
data OneEraTipInfo xs where Source #
pattern DegenTipInfo ∷ ∀ b. NoHardForks b ⇒ TipInfo b → OneEraTipInfo '[b] |
Instances
CanHardFork xs ⇒ Show (OneEraTipInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras showsPrec ∷ Int → OneEraTipInfo xs → ShowS # show ∷ OneEraTipInfo xs → String # showList ∷ [OneEraTipInfo xs] → ShowS # | |
CanHardFork xs ⇒ Eq (OneEraTipInfo xs) Source # | |
Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras (==) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # (/=) ∷ OneEraTipInfo xs → OneEraTipInfo xs → Bool # | |
CanHardFork xs ⇒ NoThunks (OneEraTipInfo xs) Source # | |
data TopLevelConfig blk where Source #
The top-level node configuration
pattern DegenTopLevelConfig ∷ NoHardForks b ⇒ TopLevelConfig b → TopLevelConfig (HardForkBlock '[b]) |
Instances
data family TxId tx ∷ Type Source #
A generalized transaction, GenTx
, identifier.