ouroboros-consensus-0.1.0.1: Consensus layer for the Ouroboros blockchain protocol
Safe Haskell None
Language Haskell2010

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

CanHardFork xs => NoThunks ( BlockConfig ( 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

data BlockConfig ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family BlockQuery blk :: Type -> Type 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

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

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

SerialiseHFC xs => SerialiseResult ( HardForkBlock xs) ( BlockQuery ( HardForkBlock xs)) Source #
Instance details

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

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

( forall 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

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

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

( Typeable m, Typeable a) => ShowProxy ( BlockQuery ( DualBlock m a) :: Type -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Typeable xs => ShowProxy ( BlockQuery ( HardForkBlock xs) :: Type -> Type ) 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

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

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => NoThunks ( CodecConfig ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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

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

Defined in Ouroboros.Consensus.Protocol.BFT

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Protocol.PBFT

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

Defined in Ouroboros.Consensus.Protocol.ModChainSel

BftCrypto c => NoThunks ( ConsensusConfig ( Bft c)) Source #
Instance details

Defined in Ouroboros.Consensus.Protocol.BFT

CanHardFork xs => NoThunks ( ConsensusConfig ( HardForkProtocol xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Protocol.PBFT

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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 ( 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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 ( 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 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 DegenQueryResult :: result -> HardForkQueryResult '[b] result

Instances

Instances details
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 #

Bitraversable Either

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: Applicative 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

bifold :: Monoid m => Either m m -> m Source #

bifoldMap :: Monoid 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 #

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

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 ) -> Int -> Either 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

MonadError e ( Either e)
Instance details

Defined in Control.Monad.Error.Class

( Lift a, Lift b) => Lift ( Either a b :: Type )
Instance details

Defined in Language.Haskell.TH.Syntax

Monad ( Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

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

Foldable ( Either a)

Since: base-4.7.0.0

Instance details

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 #

sum :: Num a0 => Either a a0 -> a0 Source #

product :: Num a0 => Either a a0 -> a0 Source #

Traversable ( Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f ( Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f ( Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m ( Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m ( Either a a0) Source #

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

Read a => Read1 ( Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Show a => Show1 ( Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

MonadFailure ( Either a)
Instance details

Defined in Basement.Monad

Associated Types

type Failure ( Either a) 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 ~ SomeException => MonadThrow ( Either e)
Instance details

Defined in Control.Monad.Catch

e ~ SomeException => MonadCatch ( Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => Either e a -> (e0 -> Either e a) -> Either e a Source #

e ~ SomeException => MonadMask ( Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask :: (( forall a. Either e a -> Either e a) -> Either e b) -> Either e b Source #

uninterruptibleMask :: (( forall a. Either e a -> Either e a) -> Either e b) -> Either e b Source #

generalBracket :: Either 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

Generic1 ( Either a :: Type -> Type )

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 ( Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 ( Either a) a0 -> Either a a0 Source #

( Eq a, Eq b) => Eq ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

( Ord a, Ord b) => Ord ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

( 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

Generic ( Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( Either a b) :: Type -> Type Source #

Semigroup ( Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

( Hashable a, Hashable b) => Hashable ( Either a b)
Instance details

Defined in Data.Hashable.Class

( Binary a, Binary b) => Binary ( Either a b)
Instance details

Defined in Data.Binary.Class

( ToCBOR a, ToCBOR b) => ToCBOR ( Either a b)
Instance details

Defined in Cardano.Binary.ToCBOR

( FromCBOR a, FromCBOR b) => FromCBOR ( Either a b)
Instance details

Defined in Cardano.Binary.FromCBOR

( NFData a, NFData b) => NFData ( Either a b)
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Either a b -> () Source #

( NoThunks a, NoThunks b) => NoThunks ( Either a b)
Instance details

Defined in NoThunks.Class

( Serialise a, Serialise b) => Serialise ( Either a b)

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

Recursive ( Either a b)
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Either a b -> Base ( Either a b) ( Either a b) Source #

cata :: ( Base ( Either a b) a0 -> a0) -> Either a b -> a0 Source #

para :: ( Base ( Either a b) ( Either a b, a0) -> a0) -> Either a b -> a0 Source #

gpara :: ( Corecursive ( Either a b), Comonad w) => ( forall b0. Base ( Either a b) (w b0) -> w ( Base ( Either a b) b0)) -> ( Base ( Either a b) ( EnvT ( Either a b) w a0) -> a0) -> Either a b -> a0 Source #

prepro :: Corecursive ( Either a b) => ( forall b0. Base ( Either a b) b0 -> Base ( Either a b) b0) -> ( Base ( Either a b) a0 -> a0) -> Either a b -> a0 Source #

gprepro :: ( Corecursive ( Either a b), Comonad w) => ( forall b0. Base ( Either a b) (w b0) -> w ( Base ( Either a b) b0)) -> ( forall c. Base ( Either a b) c -> Base ( Either a b) c) -> ( Base ( Either a b) (w a0) -> a0) -> Either a b -> a0 Source #

Corecursive ( Either a b)
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base ( Either a b) ( Either a b) -> Either a b Source #

ana :: (a0 -> Base ( Either a b) a0) -> a0 -> Either a b Source #

apo :: (a0 -> Base ( Either a b) ( Either ( Either a b) a0)) -> a0 -> Either a b Source #

postpro :: Recursive ( Either a b) => ( forall b0. Base ( Either a b) b0 -> Base ( Either a b) b0) -> (a0 -> Base ( Either a b) a0) -> a0 -> Either a b Source #

gpostpro :: ( Recursive ( Either a b), Monad m) => ( forall b0. m ( Base ( Either a b) b0) -> Base ( Either a b) (m b0)) -> ( forall c. Base ( Either a b) c -> Base ( Either a b) c) -> (a0 -> Base ( Either a b) (m a0)) -> a0 -> Either a b Source #

( 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 Source #

( 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 Source #

( 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 Source #

type Failure ( Either a)
Instance details

Defined in Basement.Monad

type Failure ( Either a) = a
type Rep1 ( Either a :: Type -> Type )
Instance details

Defined in GHC.Generics

type Rep ( Either a b)
Instance details

Defined in GHC.Generics

type Base ( Either a b)

Example boring stub for non-recursive data types

Instance details

Defined in Data.Functor.Foldable

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

Inject GenTx Source #
Instance details

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

( Typeable m, Typeable a) => ShowProxy ( TxId ( GenTx ( DualBlock m a)) :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

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

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

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

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => NoThunks ( GenTx ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

CanHardFork xs => HasTxId ( GenTx ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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 :: forall 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

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' False ) ( C1 (' MetaCons "HardForkApplyTxErrFromEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( OneEraApplyTxErr xs))) :+: C1 (' MetaCons "HardForkApplyTxErrWrongEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( MismatchEraInfo xs))))

data HardForkBlock xs where Source #

Bundled Patterns

pattern DegenBlock :: forall 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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => NoThunks ( Header ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs => NoThunks ( StorageConfig ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs => NoThunks ( CodecConfig ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs => NoThunks ( BlockConfig ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

CanHardFork xs => NoThunks ( LedgerState ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs => NoThunks ( GenTx ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

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

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

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

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

CanHardFork xs => LedgerSupportsProtocol ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

All SingleEraBlock xs => HasHardForkHistory ( 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

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

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

SerialiseHFC xs => DecodeDisk ( HardForkBlock xs) ( HardForkChainDepState xs) Source #
Instance details

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

SerialiseHFC xs => DecodeDisk ( HardForkBlock xs) ( AnnTip ( HardForkBlock xs)) Source #
Instance details

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

SerialiseHFC xs => EncodeDisk ( HardForkBlock xs) ( LedgerState ( HardForkBlock xs)) Source #
Instance details

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

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

SerialiseHFC xs => EncodeDisk ( HardForkBlock xs) ( HardForkBlock xs) Source #
Instance details

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

SerialiseHFC xs => SerialiseResult ( HardForkBlock xs) ( BlockQuery ( HardForkBlock xs)) Source #
Instance details

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

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) ( ByteString -> HardForkBlock xs) Source #
Instance details

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Typeable xs => ShowProxy ( BlockQuery ( HardForkBlock xs) :: Type -> Type ) 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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 #

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

CanHardFork xs => NoThunks ( HardForkEnvelopeErr xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' False ) ( C1 (' MetaCons "HardForkEnvelopeErrFromEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( OneEraEnvelopeErr xs))) :+: C1 (' MetaCons "HardForkEnvelopeErrWrongEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( MismatchEraInfo xs))))

data HardForkLedgerConfig xs where Source #

data HardForkLedgerError xs where Source #

Bundled Patterns

pattern DegenLedgerError :: forall 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

CanHardFork xs => NoThunks ( HardForkLedgerError xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' False ) ( C1 (' MetaCons "HardForkLedgerErrorFromEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( OneEraLedgerError xs))) :+: C1 (' MetaCons "HardForkLedgerErrorWrongEra" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe 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

Inject Header Source #
Instance details

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

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

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => NoThunks ( 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

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

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

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

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

Bridge m a => HasHeader ( DualHeader m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type HeaderHash ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type BlockProtocol ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family LedgerState blk :: Type Source #

Ledger state associated with a block

Instances

Instances details
Isomorphic LedgerState Source #
Instance details

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

Inject LedgerState Source #
Instance details

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

( Eq ( LedgerState m), Eq ( LedgerState a), Bridge m a) => Eq ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => Eq ( LedgerState ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

( Show ( LedgerState m), Show ( LedgerState a), Bridge m a) => Show ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => Show ( LedgerState ( 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

NoThunks ( Ticked ( LedgerState ( DualBlock m a))) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => NoThunks ( LedgerState ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Bridge m a => IsLedger ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => IsLedger ( LedgerState ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a => GetTip ( Ticked ( LedgerState ( DualBlock m a))) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a => GetTip ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs => GetTip ( LedgerState ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => ApplyBlock ( LedgerState ( HardForkBlock xs)) ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

SerialiseHFC xs => DecodeDisk ( HardForkBlock xs) ( LedgerState ( HardForkBlock xs)) Source #
Instance details

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

SerialiseHFC xs => EncodeDisk ( HardForkBlock xs) ( LedgerState ( HardForkBlock xs)) Source #
Instance details

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

Bridge m a => ApplyBlock ( LedgerState ( DualBlock m a)) ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Isomorphic ( Ticked :.: LedgerState ) Source #
Instance details

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

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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 HeaderHash ( LedgerState blk) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

newtype LedgerState ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerErr ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerCfg ( LedgerState ( DualBlock m a)) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data LedgerState ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data TopLevelConfig blk where Source #

The top-level node configuration

Instances

Instances details
Isomorphic TopLevelConfig Source #

Projection/injection for TopLevelConfig

NOTE: We do not define one for LedgerConfig or ConsensusConfig , since we need the EraParams for their injections, which we can only derive if we have the top-level config.

Instance details

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

Generic ( TopLevelConfig blk) Source #
Instance details

Defined in Ouroboros.Consensus.Config

Associated Types

type Rep ( TopLevelConfig blk) :: Type -> Type Source #

( ConsensusProtocol ( BlockProtocol blk), NoThunks ( LedgerConfig blk), NoThunks ( BlockConfig blk), NoThunks ( CodecConfig blk), NoThunks ( StorageConfig blk)) => NoThunks ( TopLevelConfig blk) Source #
Instance details

Defined in Ouroboros.Consensus.Config

type Rep ( TopLevelConfig blk) Source #
Instance details

Defined in Ouroboros.Consensus.Config

data family TxId tx :: Type Source #

A generalized transaction, GenTx , identifier.

Instances

Instances details
( Typeable m, Typeable a) => ShowProxy ( TxId ( GenTx ( DualBlock m a)) :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Typeable xs => ShowProxy ( TxId ( GenTx ( HardForkBlock xs)) :: Type ) 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

CanHardFork xs => Eq ( TxId ( 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

CanHardFork xs => Ord ( TxId ( 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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

SerialiseHFC xs => SerialiseNodeToClient ( HardForkBlock xs) ( GenTxId ( 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

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' True ) ( C1 (' MetaCons "HardForkGenTxId" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "getHardForkGenTxId") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( OneEraGenTxId xs))))
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