ouroboros-consensus-0.3.1.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.HardFork.Combinator.Degenerate

Synopsis

Pattern synonyms

data family BlockConfig blk ∷ Type Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

NoThunks (BlockConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → BlockConfig (DualBlock m a) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (DualBlock m a) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (DualBlock m a)) → String #

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (HardForkBlock xs)) → String #

newtype BlockConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family BlockQuery blk ∷ TypeType Source #

Different queries supported by the ledger, indexed by the result type.

Instances

Instances details
ShowQuery (BlockQuery (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showResultBlockQuery (DualBlock m a) result → result → String Source #

All SingleEraBlock xs ⇒ ShowQuery (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Methods

showResultBlockQuery (HardForkBlock xs) result → result → String Source #

SameDepIndex (BlockQuery (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexBlockQuery (DualBlock m a) a0 → BlockQuery (DualBlock m a) b → Maybe (a0 :~: b) Source #

All SingleEraBlock xs ⇒ SameDepIndex (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Inject (SomeSecond BlockQuery) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → SomeSecond BlockQuery x → SomeSecond BlockQuery (HardForkBlock xs) Source #

SerialiseHFC xs ⇒ SerialiseResult (HardForkBlock xs) (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

Methods

encodeResultCodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → BlockQuery (HardForkBlock xs) result → result → Encoding Source #

decodeResultCodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → BlockQuery (HardForkBlock xs) result → ∀ s. Decoder s result Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (SomeSecond BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SameDepIndex (BlockQuery blk) ⇒ Eq (SomeSecond BlockQuery blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

(∀ result. Show (BlockQuery blk result)) ⇒ Show (SomeSecond BlockQuery blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Show (BlockQuery (DualBlock m a) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntBlockQuery (DualBlock m a) result → ShowS Source #

showBlockQuery (DualBlock m a) result → String Source #

showList ∷ [BlockQuery (DualBlock m a) result] → ShowS Source #

All SingleEraBlock xs ⇒ Show (BlockQuery (HardForkBlock xs) result) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Methods

showsPrecIntBlockQuery (HardForkBlock xs) result → ShowS Source #

showBlockQuery (HardForkBlock xs) result → String Source #

showList ∷ [BlockQuery (HardForkBlock xs) result] → ShowS Source #

(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Typeable xs ⇒ ShowProxy (BlockQuery (HardForkBlock xs) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) a Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) a where
data BlockQuery (DualBlock m a) result Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) result

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

Instances details
Isomorphic CodecConfig Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (CodecConfig (DualBlock m a)) ∷ TypeType Source #

(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → CodecConfig (DualBlock m a) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (DualBlock m a) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (DualBlock m a)) → String #

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (HardForkBlock xs)) → String #

type Rep (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a))))
newtype CodecConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Instances details
Generic (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

Associated Types

type Rep (ConsensusConfig (ModChainSel p s)) ∷ TypeType Source #

Generic (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Associated Types

type Rep (ConsensusConfig (Bft c)) ∷ TypeType Source #

Generic (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (ConsensusConfig (HardForkProtocol xs)) ∷ TypeType Source #

Generic (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) ∷ TypeType Source #

ConsensusProtocol p ⇒ NoThunks (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

Methods

noThunks ∷ Context → ConsensusConfig (ModChainSel p s) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (ModChainSel p s) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (ModChainSel p s)) → String #

BftCrypto c ⇒ NoThunks (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

Methods

noThunks ∷ Context → ConsensusConfig (Bft c) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (Bft c) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (Bft c)) → String #

CanHardFork xs ⇒ NoThunks (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → ConsensusConfig (HardForkProtocol xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (HardForkProtocol xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (HardForkProtocol xs)) → String #

NoThunks (ConsensusConfig (PBft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ConsensusConfig (PBft c) → IO (Maybe ThunkInfo) #

showTypeOfProxy (ConsensusConfig (PBft c)) → String #

type Rep (ConsensusConfig (ModChainSel p s)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

type Rep (ConsensusConfig (ModChainSel p s)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.ModChainSel" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "McsConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "mcsConfigP") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ConsensusConfig p))))
type Rep (ConsensusConfig (Bft c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

type Rep (ConsensusConfig (Bft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.BFT" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "BftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "bftParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BftParams) :*: (S1 ('MetaSel ('Just "bftSignKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignKeyDSIGN (BftDSIGN c))) :*: S1 ('MetaSel ('Just "bftVerKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map NodeId (VerKeyDSIGN (BftDSIGN c)))))))
type Rep (ConsensusConfig (HardForkProtocol xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (ConsensusConfig (HardForkProtocol xs)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "HardForkConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkConsensusConfigK") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (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)) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
data ConsensusConfig (Bft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

data ConsensusConfig (Bft c) = BftConfig {}
data ConsensusConfig (HardForkProtocol xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype ConsensusConfig (PBft c) Source #

(Static) node configuration

Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype ConsensusConfig (ModChainSel p s) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.ModChainSel

data Either a b where Source #

The Either type represents values with two possibilities: a value of type Either a b is either Left a or 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

Expand

The type Either String Int is the type of values which can be either a String or an Int. The Left constructor can be used only on Strings, and the Right constructor can be used only on Ints:

>>> 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 Ints.

>>> :{
    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 DegenQueryResult ∷ result → HardForkQueryResult '[b] result 

Instances

Instances details
Bitraversable Either

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverseApplicative f ⇒ (a → f c) → (b → f d) → Either a b → f (Either c d) Source #

Bifoldable Either

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifoldMonoid m ⇒ Either m m → m Source #

bifoldMapMonoid m ⇒ (a → m) → (b → m) → Either a b → m Source #

bifoldr ∷ (a → c → c) → (b → c → c) → c → Either a b → c Source #

bifoldl ∷ (c → a → c) → (c → b → c) → c → Either a b → c Source #

Bifunctor Either

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap ∷ (a → b) → (c → d) → Either a c → Either b d Source #

first ∷ (a → b) → Either a c → Either b c Source #

second ∷ (b → c) → Either a b → Either a c Source #

Eq2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 ∷ (a → b → Bool) → (c → d → Bool) → Either a c → Either b d → Bool Source #

Ord2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 ∷ (a → b → Ordering) → (c → d → Ordering) → Either a c → Either b d → Ordering Source #

Read2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 ∷ (IntReadS a) → ReadS [a] → (IntReadS b) → ReadS [b] → IntReadS (Either a b) Source #

liftReadList2 ∷ (IntReadS a) → ReadS [a] → (IntReadS b) → ReadS [b] → ReadS [Either a b] Source #

liftReadPrec2ReadPrec a → ReadPrec [a] → ReadPrec b → ReadPrec [b] → ReadPrec (Either a b) Source #

liftReadListPrec2ReadPrec a → ReadPrec [a] → ReadPrec b → ReadPrec [b] → ReadPrec [Either a b] Source #

Show2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 ∷ (Int → a → ShowS) → ([a] → ShowS) → (Int → b → ShowS) → ([b] → ShowS) → IntEither a b → ShowS Source #

liftShowList2 ∷ (Int → a → ShowS) → ([a] → ShowS) → (Int → b → ShowS) → ([b] → ShowS) → [Either a b] → ShowS Source #

NFData2 Either

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 ∷ (a → ()) → (b → ()) → Either a b → () Source #

Hashable2 Either 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt2 ∷ (Int → a → Int) → (Int → b → Int) → IntEither a b → Int

MonadError e (Either e) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError ∷ e → Either e a Source #

catchErrorEither e a → (e → Either e a) → Either e a Source #

(Lift a, Lift b) ⇒ Lift (Either a b ∷ Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftEither a b → Q Exp Source #

liftTypedEither a b → Q (TExp (Either a b)) Source #

Monad (Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

Methods

(>>=)Either e a → (a → Either e b) → Either e b Source #

(>>)Either e a → Either e b → Either e b Source #

return ∷ a → Either e a Source #

Functor (Either a)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

fmap ∷ (a0 → b) → Either a a0 → Either a b Source #

(<$) ∷ a0 → Either a b → Either a a0 Source #

MonadFix (Either e)

Since: base-4.3.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix ∷ (a → Either e a) → Either e a Source #

Applicative (Either e)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

pure ∷ a → Either e a Source #

(<*>)Either e (a → b) → Either e a → Either e b Source #

liftA2 ∷ (a → b → c) → Either e a → Either e b → Either e c Source #

(*>)Either e a → Either e b → Either e b Source #

(<*)Either e a → Either e b → Either e a Source #

Foldable (Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

foldMonoid m ⇒ Either a m → m Source #

foldMapMonoid 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 #

toListEither a a0 → [a0] Source #

nullEither a a0 → Bool Source #

lengthEither a a0 → Int Source #

elemEq a0 ⇒ a0 → Either a a0 → Bool Source #

maximumOrd a0 ⇒ Either a a0 → a0 Source #

minimumOrd a0 ⇒ Either a a0 → a0 Source #

sumNum a0 ⇒ Either a a0 → a0 Source #

productNum a0 ⇒ Either a a0 → a0 Source #

Traversable (Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverseApplicative f ⇒ (a0 → f b) → Either a a0 → f (Either a b) Source #

sequenceAApplicative f ⇒ Either a (f a0) → f (Either a a0) Source #

mapMMonad m ⇒ (a0 → m b) → Either a a0 → m (Either a b) Source #

sequenceMonad m ⇒ Either a (m a0) → m (Either a a0) Source #

Eq a ⇒ Eq1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq ∷ (a0 → b → Bool) → Either a a0 → Either a b → Bool Source #

Ord a ⇒ Ord1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare ∷ (a0 → b → Ordering) → Either a a0 → Either a b → Ordering Source #

Read a ⇒ Read1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec ∷ (IntReadS a0) → ReadS [a0] → IntReadS (Either a a0) Source #

liftReadList ∷ (IntReadS a0) → ReadS [a0] → ReadS [Either a a0] Source #

liftReadPrecReadPrec a0 → ReadPrec [a0] → ReadPrec (Either a a0) Source #

liftReadListPrecReadPrec a0 → ReadPrec [a0] → ReadPrec [Either a a0] Source #

Show a ⇒ Show1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec ∷ (Int → a0 → ShowS) → ([a0] → ShowS) → IntEither a a0 → ShowS Source #

liftShowList ∷ (Int → a0 → ShowS) → ([a0] → ShowS) → [Either a a0] → ShowS Source #

NFData a ⇒ NFData1 (Either a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf ∷ (a0 → ()) → Either a a0 → () Source #

e ~ SomeExceptionMonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwMException e0 ⇒ e0 → Either e a Source #

e ~ SomeExceptionMonadCatch (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

catchException e0 ⇒ Either e a → (e0 → Either e a) → Either e a Source #

e ~ SomeExceptionMonadMask (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask ∷ ((∀ a. Either e a → Either e a) → Either e b) → Either e b Source #

uninterruptibleMask ∷ ((∀ a. Either e a → Either e a) → Either e b) → Either e b Source #

generalBracketEither e a → (a → ExitCase b → Either e c) → (a → Either e b) → Either e (b, c) Source #

Hashable a ⇒ Hashable1 (Either a) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt ∷ (Int → a0 → Int) → IntEither a a0 → Int

MonadFailure (Either a) 
Instance details

Defined in Basement.Monad

Associated Types

type Failure (Either a)

Methods

mFail ∷ Failure (Either a) → Either a ()

Generic1 (Either a ∷ TypeType)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Either a) ∷ k → Type Source #

Methods

from1 ∷ ∀ (a0 ∷ k). Either a a0 → Rep1 (Either a) a0 Source #

to1 ∷ ∀ (a0 ∷ k). Rep1 (Either a) a0 → Either a a0 Source #

MonadBaseControl (Either e) (Either e) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (Either e) a

Methods

liftBaseWith ∷ (RunInBase (Either e) (Either e) → Either e a) → Either e a

restoreM ∷ StM (Either e) a → Either e a

(Eq a, Eq b) ⇒ Eq (Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Methods

(==)Either a b → Either a b → Bool Source #

(/=)Either a b → Either a b → Bool Source #

(Ord a, Ord b) ⇒ Ord (Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Methods

compareEither 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 #

maxEither a b → Either a b → Either a b Source #

minEither a b → Either a b → Either a b Source #

(Read a, Read b) ⇒ Read (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

(Show a, Show b) ⇒ Show (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrecIntEither a b → ShowS Source #

showEither a b → String Source #

showList ∷ [Either a b] → ShowS Source #

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) ∷ TypeType Source #

Methods

fromEither a b → Rep (Either a b) x Source #

toRep (Either a b) x → Either a b Source #

Semigroup (Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Methods

(<>)Either a b → Either a b → Either a b Source #

sconcatNonEmpty (Either a b) → Either a b Source #

stimesIntegral b0 ⇒ b0 → Either a b → Either a b Source #

(Binary a, Binary b) ⇒ Binary (Either a b) 
Instance details

Defined in Data.Binary.Class

Methods

putEither a b → Put Source #

getGet (Either a b) Source #

putList ∷ [Either a b] → Put Source #

(NFData a, NFData b) ⇒ NFData (Either a b) 
Instance details

Defined in Control.DeepSeq

Methods

rnfEither a b → () Source #

(Hashable a, Hashable b) ⇒ Hashable (Either a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntEither a b → Int

hashEither a b → Int

(Serialise a, Serialise b) ⇒ Serialise (Either a b) 
Instance details

Defined in Codec.Serialise.Class

Methods

encodeEither a b → Encoding #

decode ∷ Decoder s (Either a b) #

encodeList ∷ [Either a b] → Encoding #

decodeList ∷ Decoder s [Either a b] #

(NoThunks a, NoThunks b) ⇒ NoThunks (Either a b) 
Instance details

Defined in NoThunks.Class

Methods

noThunks ∷ Context → Either a b → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Either a b → IO (Maybe ThunkInfo) #

showTypeOfProxy (Either a b) → String #

(FromCBOR a, FromCBOR b) ⇒ FromCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR ∷ Decoder s (Either a b)

labelProxy (Either a b) → Text

(ToCBOR a, ToCBOR b) ⇒ ToCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOREither 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) 
Instance details

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) 
Instance details

Defined in Data.Functor.Foldable

Methods

projectEither 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) 
Instance details

Defined in PlutusTx.Ord

Methods

compareEither a b → Either a b → Ordering

(<)Either a b → Either a b → Bool

(<=)Either a b → Either a b → Bool

(>)Either a b → Either a b → Bool

(>=)Either a b → Either a b → Bool

maxEither a b → Either a b → Either a b

minEither a b → Either a b → Either a b

MonoFoldable (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMapMonoid 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

otoListEither 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

onullEither a b → Bool

olengthEither a b → Int

olength64Either a b → Int64

ocompareLengthIntegral 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 ()

ofoldlMMonad m ⇒ (a0 → Element (Either a b) → m a0) → a0 → Either a b → m a0

ofoldMap1ExSemigroup 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)

headExEither a b → Element (Either a b)

lastExEither a b → Element (Either a b)

unsafeHeadEither a b → Element (Either a b)

unsafeLastEither 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)

oelem ∷ Element (Either a b) → Either a b → Bool

onotElem ∷ Element (Either a b) → Either a b → Bool

MonoTraversable (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

otraverseApplicative f ⇒ (Element (Either a b) → f (Element (Either a b))) → Either a b → f (Either a b)

omapMApplicative m ⇒ (Element (Either a b) → m (Element (Either a b))) → Either a b → m (Either a b)

MonoFunctor (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

omap ∷ (Element (Either a b) → Element (Either a b)) → Either a b → Either a b

MonoPointed (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

opoint ∷ Element (Either a b) → Either a b

(a ~ a', b ~ b') ⇒ Each (Either a a') (Either b b') a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each ∷ Traversal (Either a a') (Either b b') a b

(SemialignWithIndex i f, SemialignWithIndex j g) ⇒ SemialignWithIndex (Either i j) (Product f g) 
Instance details

Defined in Data.Semialign.Internal

Methods

ialignWith ∷ (Either i j → These a b → c) → Product f g a → Product f g b → Product f g c

(ZipWithIndex i f, ZipWithIndex j g) ⇒ ZipWithIndex (Either i j) (Product f g) 
Instance details

Defined in Data.Semialign.Internal

Methods

izipWith ∷ (Either i j → a → b → c) → Product f g a → Product f g b → Product f g c

(RepeatWithIndex i f, RepeatWithIndex j g) ⇒ RepeatWithIndex (Either i j) (Product f g) 
Instance details

Defined in Data.Semialign.Internal

Methods

irepeat ∷ (Either i j → a) → Product f g a

type Failure (Either a) 
Instance details

Defined in Basement.Monad

type Failure (Either a) = a
type StM (Either e) a 
Instance details

Defined in Control.Monad.Trans.Control

type StM (Either e) a = a
type Rep1 (Either a ∷ TypeType) 
Instance details

Defined in GHC.Generics

type Rep (Either a b) 
Instance details

Defined in GHC.Generics

type Base (Either a b) 
Instance details

Defined in Data.Functor.Foldable

type Base (Either a b) = Const (Either a b) ∷ TypeType
type Element (Either a b) 
Instance details

Defined in Data.MonoTraversable

type Element (Either a b) = b

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

Instances details
Isomorphic GenTx Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ GenTx (HardForkBlock '[blk]) → GenTx blk Source #

injectNoHardForks blk ⇒ GenTx blk → GenTx (HardForkBlock '[blk]) Source #

Inject GenTx Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → GenTx x → GenTx (HardForkBlock xs) Source #

(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → String Source #

Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

(Typeable m, Typeable a) ⇒ ShowProxy (GenTx (DualBlock m a) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (GenTx (DualBlock m a)) → String Source #

Typeable xs ⇒ ShowProxy (GenTx (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Eq (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering Source #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool Source #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) Source #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) Source #

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS Source #

showTxId (GenTx (DualBlock m a)) → String Source #

showList ∷ [TxId (GenTx (DualBlock m a))] → ShowS Source #

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ Show (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntGenTx (DualBlock m a) → ShowS Source #

showGenTx (DualBlock m a) → String Source #

showList ∷ [GenTx (DualBlock m a)] → ShowS Source #

CanHardFork xs ⇒ Show (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType Source #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType Source #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x Source #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) Source #

Generic (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (GenTx (HardForkBlock xs)) ∷ TypeType Source #

NoThunks (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → Validated (GenTx (DualBlock m a)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (DualBlock m a)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (DualBlock m a))) → String #

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → Validated (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (HardForkBlock xs))) → String #

NoThunks (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → TxId (GenTx (DualBlock m a)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (DualBlock m a)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (DualBlock m a))) → String #

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → TxId (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (HardForkBlock xs))) → String #

NoThunks (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → GenTx (DualBlock m a) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → GenTx (DualBlock m a) → IO (Maybe ThunkInfo) #

showTypeOfProxy (GenTx (DualBlock m a)) → String #

CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → GenTx (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → GenTx (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (GenTx (HardForkBlock xs)) → String #

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) Source #

CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

txIdGenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

type Rep (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
type Rep (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
data Validated (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Validated (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype TxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype GenTx (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data GenTx (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data HardForkApplyTxErr xs where Source #

Bundled Patterns

pattern DegenApplyTxErr ∷ ∀ b. NoHardForks b ⇒ ApplyTxErr b → HardForkApplyTxErr '[b] 

Instances

Instances details
CanHardFork xs ⇒ Eq (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Show (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Generic (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (HardForkApplyTxErr xs) ∷ TypeType Source #

Typeable xs ⇒ ShowProxy (HardForkApplyTxErr xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

type Rep (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (HardForkApplyTxErr xs) = D1 ('MetaData "HardForkApplyTxErr" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "HardForkApplyTxErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OneEraApplyTxErr xs))) :+: C1 ('MetaCons "HardForkApplyTxErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MismatchEraInfo xs))))

data HardForkBlock xs where Source #

Bundled Patterns

pattern DegenBlock ∷ ∀ b. NoHardForks b ⇒ b → HardForkBlock '[b] 

Instances

Instances details
Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Typeable xs ⇒ ShowProxy (GenTx (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ Eq (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Eq (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

All Eq xs ⇒ Eq (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ Show (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Show (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Show (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Generic (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (Ticked (LedgerState (HardForkBlock xs))) ∷ TypeType Source #

Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType Source #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType Source #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x Source #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) Source #

Generic (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (GenTx (HardForkBlock xs)) ∷ TypeType Source #

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ HasHeader (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ StandardHash (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

All SingleEraBlock xs ⇒ ShowQuery (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Methods

showResultBlockQuery (HardForkBlock xs) result → result → String Source #

CanHardFork xs ⇒ NoThunks (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (HardForkBlock xs))) → String #

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

noThunks ∷ Context → Header (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (HardForkBlock xs)) → String #

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig (HardForkBlock xs)) → String #

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (HardForkBlock xs)) → String #

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (HardForkBlock xs)) → String #

CanHardFork xs ⇒ NoThunks (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (HardForkBlock xs)) → String #

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → Validated (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Validated (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Validated (GenTx (HardForkBlock xs))) → String #

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → TxId (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TxId (GenTx (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (TxId (GenTx (HardForkBlock xs))) → String #

CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

noThunks ∷ Context → GenTx (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → GenTx (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (GenTx (HardForkBlock xs)) → String #

SerialiseHFC xs ⇒ HasNetworkProtocolVersion (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common

All SingleEraBlock xs ⇒ SameDepIndex (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

CanHardFork xs ⇒ ConvertRawHash (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ GetHeader (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ GetPrevHash (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ IsLedger (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ GetTip (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ UpdateLedger (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ LedgerSupportsPeerSelection (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.PeerSelection

CanHardFork xs ⇒ CommonProtocolParams (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.CommonProtocolParams

CanHardFork xs ⇒ BlockSupportsProtocol (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

CanHardFork xs ⇒ BlockSupportsMetrics (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.Metrics

All HasTxs xs ⇒ HasTxs (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

txIdGenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source #

CanHardFork xs ⇒ LedgerSupportsMempool (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ ValidateEnvelope (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ BasicEnvelopeValidation (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ HasAnnTip (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Associated Types

type TipInfo (HardForkBlock xs) Source #

CanHardFork xs ⇒ InspectLedger (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

SerialiseHFC xs ⇒ HasBinaryBlockInfo (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

All SingleEraBlock xs ⇒ HasHardForkHistory (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type HardForkIndices (HardForkBlock xs) ∷ [Type] Source #

CanHardFork xs ⇒ LedgerSupportsProtocol (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ ConfigSupportsNode (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node

All SingleEraBlock xs ⇒ QueryLedger (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

CanHardFork xs ⇒ NodeInitStorage (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node.InitStorage

SerialiseHFC xs ⇒ SerialiseDiskConstraints (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

(CanHardFork xs, SupportedNetworkProtocolVersion (HardForkBlock xs), SerialiseHFC xs) ⇒ RunNode (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Node

SerialiseHFC xs ⇒ SerialiseNodeToClientConstraints (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToNodeConstraints (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) SlotNo Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

Typeable xs ⇒ ShowProxy (HardForkBlock xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs ⇒ ApplyBlock (LedgerState (HardForkBlock xs)) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskDepCodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → ∀ s. Decoder s (ByteString → a) Source #

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

encodeDiskDepCodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → a → Encoding Source #

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskCodecConfig (HardForkBlock xs) → ∀ s. Decoder s (LedgerState (HardForkBlock xs)) Source #

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskCodecConfig (HardForkBlock xs) → ∀ s. Decoder s (HardForkChainDepState xs) Source #

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (AnnTip (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskCodecConfig (HardForkBlock xs) → ∀ s. Decoder s (AnnTip (HardForkBlock xs)) Source #

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

encodeDiskCodecConfig (HardForkBlock xs) → LedgerState (HardForkBlock xs) → Encoding Source #

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (AnnTip (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

encodeDiskCodecConfig (HardForkBlock xs) → AnnTip (HardForkBlock xs) → Encoding Source #

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

encodeDiskCodecConfig (HardForkBlock xs) → HardForkBlock xs → Encoding Source #

SerialiseHFC xs ⇒ SerialiseResult (HardForkBlock xs) (BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

Methods

encodeResultCodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → BlockQuery (HardForkBlock xs) result → result → Encoding Source #

decodeResultCodecConfig (HardForkBlock xs) → BlockNodeToClientVersion (HardForkBlock xs) → BlockQuery (HardForkBlock xs) result → ∀ s. Decoder s result Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (HardForkApplyTxErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (Serialised (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (SerialisedHeader (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Serialised (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (ByteStringHardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskCodecConfig (HardForkBlock xs) → ∀ s. Decoder s (ByteStringHardForkBlock xs) Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (SomeSecond BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

All SingleEraBlock xs ⇒ Show (BlockQuery (HardForkBlock xs) result) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

Methods

showsPrecIntBlockQuery (HardForkBlock xs) result → ShowS Source #

showBlockQuery (HardForkBlock xs) result → String Source #

showList ∷ [BlockQuery (HardForkBlock xs) result] → ShowS Source #

CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Typeable xs ⇒ ShowProxy (BlockQuery (HardForkBlock xs) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
type Rep (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.3.1.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type HeaderHash (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type BlockNodeToNodeVersion (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common

type BlockNodeToClientVersion (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common

data Ticked (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data NestedCtxt_ (HardForkBlock xs) a b Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
newtype Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype StorageConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype CodecConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype BlockConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type BlockProtocol (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype LedgerState (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerErr (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerCfg (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype Validated (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type ApplyTxErr (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype GenTx (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type ForgeStateUpdateError (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type ForgeStateInfo (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type CannotForge (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type OtherHeaderEnvelopeError (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TipInfo (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type LedgerWarning (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerUpdate (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type HardForkIndices (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data BlockQuery (HardForkBlock xs) a Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) a where

data HardForkEnvelopeErr xs where Source #

Bundled Patterns

pattern DegenOtherHeaderEnvelopeError ∷ ∀ b. NoHardForks b ⇒ OtherHeaderEnvelopeError b → HardForkEnvelopeErr '[b] 

Instances

Instances details
CanHardFork xs ⇒ Eq (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ Show (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Generic (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkEnvelopeErr xs) ∷ TypeType Source #

CanHardFork xs ⇒ NoThunks (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks ∷ Context → HardForkEnvelopeErr xs → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → HardForkEnvelopeErr xs → IO (Maybe ThunkInfo) #

showTypeOfProxy (HardForkEnvelopeErr xs) → String #

type Rep (HardForkEnvelopeErr xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkEnvelopeErr xs) = D1 ('MetaData "HardForkEnvelopeErr" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "HardForkEnvelopeErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraEnvelopeErr xs))) :+: C1 ('MetaCons "HardForkEnvelopeErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

data HardForkLedgerConfig xs where Source #

Bundled Patterns

pattern DegenLedgerConfigPartialLedgerConfig b → HardForkLedgerConfig '[b] 

Instances

Instances details
Generic (HardForkLedgerConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (HardForkLedgerConfig xs) ∷ TypeType Source #

CanHardFork xs ⇒ NoThunks (HardForkLedgerConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → HardForkLedgerConfig xs → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → HardForkLedgerConfig xs → IO (Maybe ThunkInfo) #

showTypeOfProxy (HardForkLedgerConfig xs) → String #

type Rep (HardForkLedgerConfig xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (HardForkLedgerConfig xs) = D1 ('MetaData "HardForkLedgerConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.3.1.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 #

Bundled Patterns

pattern DegenLedgerError ∷ ∀ b. NoHardForks b ⇒ LedgerError b → HardForkLedgerError '[b] 

Instances

Instances details
CanHardFork xs ⇒ Eq (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs ⇒ Show (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Generic (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkLedgerError xs) ∷ TypeType Source #

CanHardFork xs ⇒ NoThunks (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks ∷ Context → HardForkLedgerError xs → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → HardForkLedgerError xs → IO (Maybe ThunkInfo) #

showTypeOfProxy (HardForkLedgerError xs) → String #

type Rep (HardForkLedgerError xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkLedgerError xs) = D1 ('MetaData "HardForkLedgerError" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.3.1.0-inplace" 'False) (C1 ('MetaCons "HardForkLedgerErrorFromEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraLedgerError xs))) :+: C1 ('MetaCons "HardForkLedgerErrorWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

data family Header blk ∷ Type Source #

Instances

Instances details
Isomorphic Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

Inject Header Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → Header x → Header (HardForkBlock xs) Source #

Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

HasHeader blk ⇒ StandardHash (Header blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

NoThunks (Header (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → Header (DualBlock m a) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (DualBlock m a) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (DualBlock m a)) → String #

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

noThunks ∷ Context → Header (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (HardForkBlock xs)) → String #

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskDepCodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → ∀ s. Decoder s (ByteString → a) Source #

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

encodeDiskDepCodecConfig (HardForkBlock xs) → NestedCtxt Header (HardForkBlock xs) a → a → Encoding Source #

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Header m) ⇒ Show (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS Source #

showDualHeader m a → String Source #

showList ∷ [DualHeader m a] → ShowS Source #

Bridge m a ⇒ HasHeader (DualHeader m a) Source