Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ChainDB m blk = ChainDB {
- addBlockAsync ∷ InvalidBlockPunishment m → blk → m (AddBlockPromise m blk)
- chainSelAsync ∷ m (ChainSelectionPromise m)
- getCurrentChain ∷ STM m (AnchoredFragment (Header blk))
- getLedgerDB ∷ STM m (LedgerDB' blk)
- getHeaderStateHistory ∷ STM m (HeaderStateHistory blk)
- getTipBlock ∷ m (Maybe blk)
- getTipHeader ∷ m (Maybe (Header blk))
- getTipPoint ∷ STM m (Point blk)
- getBlockComponent ∷ ∀ b. BlockComponent blk b → RealPoint blk → m (Maybe b)
- getIsFetched ∷ STM m (Point blk → Bool)
- getIsValid ∷ STM m (RealPoint blk → Maybe Bool)
- getMaxSlotNo ∷ STM m MaxSlotNo
- stream ∷ ∀ b. ResourceRegistry m → BlockComponent blk b → StreamFrom blk → StreamTo blk → m (Either (UnknownRange blk) (Iterator m blk b))
- newFollower ∷ ∀ b. ResourceRegistry m → ChainType → BlockComponent blk b → m (Follower m blk b)
- getIsInvalidBlock ∷ STM m (WithFingerprint (HeaderHash blk → Maybe (ExtValidationError blk)))
- closeDB ∷ m ()
- isOpen ∷ STM m Bool
- getCurrentLedger ∷ (Monad (STM m), IsLedger (LedgerState blk)) ⇒ ChainDB m blk → STM m (ExtLedgerState blk)
- getCurrentTip ∷ (Monad (STM m), HasHeader (Header blk)) ⇒ ChainDB m blk → STM m (Tip blk)
- getImmutableLedger ∷ Monad (STM m) ⇒ ChainDB m blk → STM m (ExtLedgerState blk)
- getPastLedger ∷ (Monad (STM m), LedgerSupportsProtocol blk) ⇒ ChainDB m blk → Point blk → STM m (Maybe (ExtLedgerState blk))
- getTipBlockNo ∷ (Monad (STM m), HasHeader (Header blk)) ⇒ ChainDB m blk → STM m (WithOrigin BlockNo)
- data AddBlockPromise m blk = AddBlockPromise {
- blockWrittenToDisk ∷ STM m Bool
- blockProcessed ∷ STM m (AddBlockResult blk)
- data AddBlockResult blk
- = SuccesfullyAddedBlock (Point blk)
- | FailedToAddBlock String
- addBlock ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m (AddBlockResult blk)
- addBlockWaitWrittenToDisk ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m Bool
- addBlock_ ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m ()
- newtype ChainSelectionPromise m = ChainSelectionPromise {
- waitChainSelectionPromise ∷ m ()
- triggerChainSelection ∷ IOLike m ⇒ ChainDB m blk → m ()
- triggerChainSelectionAsync ∷ ChainDB m blk → m (ChainSelectionPromise m)
- data WithPoint blk b = WithPoint {
- withoutPoint ∷ !b
- point ∷ !(Point blk)
- getPoint ∷ BlockComponent blk (Point blk)
- getSerialisedBlockWithPoint ∷ BlockComponent blk (WithPoint blk (Serialised blk))
- getSerialisedHeaderWithPoint ∷ BlockComponent blk (WithPoint blk (SerialisedHeader blk))
- data BlockComponent blk a where
- GetVerifiedBlock ∷ BlockComponent blk blk
- GetBlock ∷ BlockComponent blk blk
- GetRawBlock ∷ BlockComponent blk ByteString
- GetHeader ∷ BlockComponent blk (Header blk)
- GetRawHeader ∷ BlockComponent blk ByteString
- GetHash ∷ BlockComponent blk (HeaderHash blk)
- GetSlot ∷ BlockComponent blk SlotNo
- GetIsEBB ∷ BlockComponent blk IsEBB
- GetBlockSize ∷ BlockComponent blk SizeInBytes
- GetHeaderSize ∷ BlockComponent blk Word16
- GetNestedCtxt ∷ BlockComponent blk (SomeSecond (NestedCtxt Header) blk)
- GetPure ∷ a → BlockComponent blk a
- GetApply ∷ BlockComponent blk (a → b) → BlockComponent blk a → BlockComponent blk b
- fromChain ∷ ∀ m blk. IOLike m ⇒ m (ChainDB m blk) → Chain blk → m (ChainDB m blk)
- toChain ∷ ∀ m blk. (HasCallStack, IOLike m, HasHeader blk) ⇒ ChainDB m blk → m (Chain blk)
- data Iterator m blk b = Iterator {
- iteratorNext ∷ m (IteratorResult blk b)
- iteratorClose ∷ m ()
- data IteratorResult blk b
- = IteratorExhausted
- | IteratorResult b
- | IteratorBlockGCed (RealPoint blk)
- data StreamFrom blk
- = StreamFromInclusive !(RealPoint blk)
- | StreamFromExclusive !(Point blk)
- newtype StreamTo blk = StreamToInclusive (RealPoint blk)
- data UnknownRange blk
- = MissingBlock (RealPoint blk)
- | ForkTooOld (StreamFrom blk)
- emptyIterator ∷ Monad m ⇒ Iterator m blk b
- streamAll ∷ (MonadSTM m, HasHeader blk, HasCallStack) ⇒ ChainDB m blk → ResourceRegistry m → BlockComponent blk b → m (Iterator m blk b)
- streamFrom ∷ (MonadSTM m, HasHeader blk, HasCallStack) ⇒ StreamFrom blk → ChainDB m blk → ResourceRegistry m → BlockComponent blk b → m (Iterator m blk b)
- traverseIterator ∷ Monad m ⇒ (b → m b') → Iterator m blk b → Iterator m blk b'
- validBounds ∷ StandardHash blk ⇒ StreamFrom blk → StreamTo blk → Bool
- data ChainType
- data Follower m blk a = Follower {
- followerInstruction ∷ m (Maybe (ChainUpdate blk a))
- followerInstructionBlocking ∷ m (ChainUpdate blk a)
- followerForward ∷ [Point blk] → m (Maybe (Point blk))
- followerClose ∷ m ()
- traverseFollower ∷ Monad m ⇒ (b → m b') → Follower m blk b → Follower m blk b'
- data ChainDbFailure blk
- = LgrDbFailure FsError
- | ChainDbMissingBlock (RealPoint blk)
- data IsEBB
- data ChainDbError blk
- type GetLoEFragment m blk = m (LoE (AnchoredFragment (Header blk)))
- data LoE a
- = LoEDisabled
- | LoEEnabled !a
Main ChainDB API
The chain database
The chain database provides a unified interface on top of:
- The ImmutableDB, storing the part of the chain that can't roll back.
- The VolatileDB, storing the blocks near the tip of the chain, possibly in multiple competing forks.
- The LedgerDB, storing snapshots of the ledger state for blocks in the ImmutableDB (and in-memory snapshots for the rest).
In addition to providing a unifying interface on top of these disparate components, the main responsibilities that the ChainDB itself has are:
- Chain selection (on initialization and whenever a block is added)
- Trigger full recovery whenever we detect disk failure in any component
- Provide iterators across fixed fragments of the current chain
- Provide followers that track the status of the current chain
The ChainDB instantiates all the various type parameters of these databases to conform to the unified interface we provide here.
ChainDB | |
|
getCurrentLedger ∷ (Monad (STM m), IsLedger (LedgerState blk)) ⇒ ChainDB m blk → STM m (ExtLedgerState blk) Source #
Get current ledger
getImmutableLedger ∷ Monad (STM m) ⇒ ChainDB m blk → STM m (ExtLedgerState blk) Source #
Get the immutable ledger, i.e., typically k
blocks back.
getPastLedger ∷ (Monad (STM m), LedgerSupportsProtocol blk) ⇒ ChainDB m blk → Point blk → STM m (Maybe (ExtLedgerState blk)) Source #
Get the ledger for the given point.
When the given point is not among the last k
blocks of the current
chain (i.e., older than k
or not on the current chain), Nothing
is
returned.
getTipBlockNo ∷ (Monad (STM m), HasHeader (Header blk)) ⇒ ChainDB m blk → STM m (WithOrigin BlockNo) Source #
Adding a block
data AddBlockPromise m blk Source #
AddBlockPromise | |
|
data AddBlockResult blk Source #
This is a wrapper type for blockProcessed
function above.
As it is mentioned the SuccessfullyAddedBlock
constructor will containt
the ChainDB's tip after chain selection is returned.
The FailedToAddBlock
case will be returned if the thread adding the block
died.
Instances
StandardHash blk ⇒ Show (AddBlockResult blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API showsPrec ∷ Int → AddBlockResult blk → ShowS # show ∷ AddBlockResult blk → String # showList ∷ [AddBlockResult blk] → ShowS # | |
StandardHash blk ⇒ Eq (AddBlockResult blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API (==) ∷ AddBlockResult blk → AddBlockResult blk → Bool # (/=) ∷ AddBlockResult blk → AddBlockResult blk → Bool # |
addBlock ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m (AddBlockResult blk) Source #
Add a block synchronously: wait until the block has been processed (see
blockProcessed
). The new tip of the ChainDB is returned unless the thread adding the
block died, in that case FailedToAddBlock
will be returned.
Note: this is a partial function, only to support tests.
PRECONDITION: the block to be added must not be from the future. See addBlockAsync
.
addBlockWaitWrittenToDisk ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m Bool Source #
Add a block synchronously: wait until the block has been written to disk
(see blockWrittenToDisk
).
addBlock_ ∷ IOLike m ⇒ ChainDB m blk → InvalidBlockPunishment m → blk → m () Source #
Add a block synchronously. Variant of addBlock
that doesn't return the
new tip of the ChainDB.
Note: this is a partial function, only to support tests.
Trigger chain selection
newtype ChainSelectionPromise m Source #
A promise that the chain selection will be performed. It is returned by
triggerChainSelectionAsync
and contains a monadic action that waits until
the corresponding run of Chain Selection is done.
triggerChainSelection ∷ IOLike m ⇒ ChainDB m blk → m () Source #
Trigger selection synchronously: wait until the chain selection has been performed. This is a partial function, only to support tests.
triggerChainSelectionAsync ∷ ChainDB m blk → m (ChainSelectionPromise m) Source #
Alias for naming consistency. The short name was chosen to avoid a larger diff from alignment changes.
Serialised block/header with its point
A b
together with its Point
.
The Point
is needed because we often need to know the hash, slot, or
point itself of the block or header in question, and we don't want to
deserialise the block to obtain it.
WithPoint | |
|
Instances
StandardHash blk ⇒ StandardHash (WithPoint blk b ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API | |
type HeaderHash (WithPoint blk b ∷ Type) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API |
getPoint ∷ BlockComponent blk (Point blk) Source #
getSerialisedBlockWithPoint ∷ BlockComponent blk (WithPoint blk (Serialised blk)) Source #
getSerialisedHeaderWithPoint ∷ BlockComponent blk (WithPoint blk (SerialisedHeader blk)) Source #
BlockComponent
data BlockComponent blk a where Source #
Which component of the block to read from a database: the whole block, its header, its hash, the block size, ..., or combinations thereof.
NOTE: when requesting multiple components, we will not optimise/cache them.
GetVerifiedBlock ∷ BlockComponent blk blk | Verify the integrity of the block by checking its signature and/or hashes. The interpreter should throw an exception when the block does not pass the check. |
GetBlock ∷ BlockComponent blk blk | |
GetRawBlock ∷ BlockComponent blk ByteString | |
GetHeader ∷ BlockComponent blk (Header blk) | |
GetRawHeader ∷ BlockComponent blk ByteString | |
GetHash ∷ BlockComponent blk (HeaderHash blk) | |
GetSlot ∷ BlockComponent blk SlotNo | |
GetIsEBB ∷ BlockComponent blk IsEBB | |
GetBlockSize ∷ BlockComponent blk SizeInBytes | |
GetHeaderSize ∷ BlockComponent blk Word16 | |
GetNestedCtxt ∷ BlockComponent blk (SomeSecond (NestedCtxt Header) blk) | |
GetPure ∷ a → BlockComponent blk a | |
GetApply ∷ BlockComponent blk (a → b) → BlockComponent blk a → BlockComponent blk b |
Instances
Applicative (BlockComponent blk) Source # | |
Defined in Ouroboros.Consensus.Storage.Common pure ∷ a → BlockComponent blk a # (<*>) ∷ BlockComponent blk (a → b) → BlockComponent blk a → BlockComponent blk b # liftA2 ∷ (a → b → c) → BlockComponent blk a → BlockComponent blk b → BlockComponent blk c # (*>) ∷ BlockComponent blk a → BlockComponent blk b → BlockComponent blk b # (<*) ∷ BlockComponent blk a → BlockComponent blk b → BlockComponent blk a # | |
Functor (BlockComponent blk) Source # | |
Defined in Ouroboros.Consensus.Storage.Common fmap ∷ (a → b) → BlockComponent blk a → BlockComponent blk b # (<$) ∷ a → BlockComponent blk b → BlockComponent blk a # |
Support for tests
Iterator API
data Iterator m blk b Source #
Iterator | |
|
Instances
Foldable m ⇒ Foldable (Iterator m blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API fold ∷ Monoid m0 ⇒ Iterator m blk m0 → m0 # foldMap ∷ Monoid m0 ⇒ (a → m0) → Iterator m blk a → m0 # foldMap' ∷ Monoid m0 ⇒ (a → m0) → Iterator m blk a → m0 # foldr ∷ (a → b → b) → b → Iterator m blk a → b # foldr' ∷ (a → b → b) → b → Iterator m blk a → b # foldl ∷ (b → a → b) → b → Iterator m blk a → b # foldl' ∷ (b → a → b) → b → Iterator m blk a → b # foldr1 ∷ (a → a → a) → Iterator m blk a → a # foldl1 ∷ (a → a → a) → Iterator m blk a → a # toList ∷ Iterator m blk a → [a] # null ∷ Iterator m blk a → Bool # length ∷ Iterator m blk a → Int # elem ∷ Eq a ⇒ a → Iterator m blk a → Bool # maximum ∷ Ord a ⇒ Iterator m blk a → a # minimum ∷ Ord a ⇒ Iterator m blk a → a # | |
Traversable m ⇒ Traversable (Iterator m blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API | |
Functor m ⇒ Functor (Iterator m blk) Source # | |
data IteratorResult blk b Source #
IteratorExhausted | |
IteratorResult b | |
IteratorBlockGCed (RealPoint blk) | The block that was supposed to be streamed was garbage-collected from the VolatileDB, but not added to the ImmutableDB. This will only happen when streaming very old forks very slowly. The following example illustrates a situation in which an iterator result
could be a iterator i ↓ ... ⟶ [[ a ]] → [[ b ]] → [ c ] -> [ d ] ──────────────────────╯ ╰────────────╯ Immutable DB Current chain Suppose we switch to a longer fork that branches off from the immutable tip ('[[b]]'). iterator i ↓ ... ⟶ [[ a ]] → [[ b ]] → [ c ] -> [ d ] ──────────────────────╯│ Immutable DB │ ╰-→ [ e ] -> [ f ] -> [ g ] ╰─────────────────────╯ Current chain Assume |
Instances
data StreamFrom blk Source #
The lower bound for an iterator
Hint: use
to start streaming from
Genesis.StreamFromExclusive
genesisPoint
StreamFromInclusive !(RealPoint blk) | |
StreamFromExclusive !(Point blk) |
Instances
StreamToInclusive (RealPoint blk) |
Instances
Generic (StreamTo blk) Source # | |
StandardHash blk ⇒ Show (StreamTo blk) Source # | |
StandardHash blk ⇒ Eq (StreamTo blk) Source # | |
(StandardHash blk, Typeable blk) ⇒ NoThunks (StreamTo blk) Source # | |
type Rep (StreamTo blk) Source # | |
Defined in Ouroboros.Consensus.Storage.Common type Rep (StreamTo blk) = D1 ('MetaData "StreamTo" "Ouroboros.Consensus.Storage.Common" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "StreamToInclusive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RealPoint blk)))) |
data UnknownRange blk Source #
MissingBlock (RealPoint blk) | The block at the given point was not found in the ChainDB. |
ForkTooOld (StreamFrom blk) | The requested range forks off too far in the past, i.e. it doesn't fit on the tip of the ImmutableDB. |
Instances
StandardHash blk ⇒ Show (UnknownRange blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API showsPrec ∷ Int → UnknownRange blk → ShowS # show ∷ UnknownRange blk → String # showList ∷ [UnknownRange blk] → ShowS # | |
StandardHash blk ⇒ Eq (UnknownRange blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API (==) ∷ UnknownRange blk → UnknownRange blk → Bool # (/=) ∷ UnknownRange blk → UnknownRange blk → Bool # |
emptyIterator ∷ Monad m ⇒ Iterator m blk b Source #
An iterator that is immediately exhausted.
streamAll ∷ (MonadSTM m, HasHeader blk, HasCallStack) ⇒ ChainDB m blk → ResourceRegistry m → BlockComponent blk b → m (Iterator m blk b) Source #
Stream all blocks from the current chain.
streamFrom ∷ (MonadSTM m, HasHeader blk, HasCallStack) ⇒ StreamFrom blk → ChainDB m blk → ResourceRegistry m → BlockComponent blk b → m (Iterator m blk b) Source #
Stream blocks from the given point up to the tip from the current chain.
To stream all blocks from the current chain from the ChainDB, one would use
as the lower bound and
StreamFromExclusive
genesisPoint
as the upper bound where StreamToInclusive
tiptip
is retrieved with
getTipPoint
.
However, when the ChainDB is empty, tip
will be genesisPoint
too, in
which case the bounds don't make sense. This function correctly handles
this case.
Note that this is not a Follower
, so the stream will not include blocks
that are added to the current chain after starting the stream.
traverseIterator ∷ Monad m ⇒ (b → m b') → Iterator m blk b → Iterator m blk b' Source #
Variant of traverse
instantiated to
that executes
the monadic function when calling Iterator
m blkiteratorNext
.
validBounds ∷ StandardHash blk ⇒ StreamFrom blk → StreamTo blk → Bool Source #
Check whether the bounds make sense
An example of bounds that don't make sense:
StreamFromExclusive (BlockPoint 3 ..) StreamToInclusive (RealPoint 3 ..)
This function does not check whether the bounds correspond to existing blocks.
Followers
Chain type
Follower
s can choose to track changes to the "normal" SelectedChain
, or
track the TentativeChain
, which might contain a pipelineable header at the
tip.
data Follower m blk a Source #
Follower
Unlike an Iterator
, which is used to request a static segment of the
current chain or a recent fork, a follower is used to follow the
current chain either from the start or from a given point.
Unlike an Iterator
, a Follower
is dynamic, that is, it will follow
the chain when it grows or forks.
A follower is pull-based, which avoids the neeed to have a growing queue of changes to the chain on the server side in case the client is slower.
A follower always has an implicit position associated with it. The
followerInstruction
and followerInstructionBlocking
operations request
the next ChainUpdate
wrt the follower's implicit position.
The type parameter a
will be instantiated with blk
or
.Header
blk
Follower | |
|
traverseFollower ∷ Monad m ⇒ (b → m b') → Follower m blk b → Follower m blk b' Source #
Variant of traverse
instantiated to
that executes the
monadic function when calling Follower
m blkfollowerInstruction
and
followerInstructionBlocking
.
Recovery
data ChainDbFailure blk Source #
Database failure
This exception wraps any kind of unexpected problem with the on-disk storage of the chain.
The various constructors only serve to give more detailed information about what went wrong, in case sysadmins want to investigate the disk failure. The Chain DB itself does not differentiate; all disk failures are treated equal and all trigger the same recovery procedure.
LgrDbFailure FsError | The ledger DB threw a file-system error |
ChainDbMissingBlock (RealPoint blk) | Block missing from the chain DB Thrown when we are not sure in which DB the block should have been. |
Instances
(Typeable blk, StandardHash blk) ⇒ Exception (ChainDbFailure blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API toException ∷ ChainDbFailure blk → SomeException # fromException ∷ SomeException → Maybe (ChainDbFailure blk) # displayException ∷ ChainDbFailure blk → String # | |
StandardHash blk ⇒ Show (ChainDbFailure blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API showsPrec ∷ Int → ChainDbFailure blk → ShowS # show ∷ ChainDbFailure blk → String # showList ∷ [ChainDbFailure blk] → ShowS # |
Whether a block is an Epoch Boundary Block (EBB)
See Ouroboros.Storage.ImmutableDB.API for a discussion of EBBs. Key idiosyncracies:
- An EBB carries no unique information.
- An EBB has the same
BlockNo
as its predecessor. - EBBs are vestigial. As of Shelley, nodes no longer forge EBBs: they are only a legacy/backwards-compatibility concern.
Exceptions
data ChainDbError blk Source #
Database error
Thrown upon incorrect use: invalid input.
ClosedDBError PrettyCallStack | The ChainDB is closed. This will be thrown when performing any operation on the ChainDB except
for |
ClosedFollowerError | The follower is closed. This will be thrown when performing any operation on a closed followers,
except for |
InvalidIteratorRange (StreamFrom blk) (StreamTo blk) | When there is no chain/fork that satisfies the bounds passed to
|
Instances
(Typeable blk, StandardHash blk) ⇒ Exception (ChainDbError blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API toException ∷ ChainDbError blk → SomeException # fromException ∷ SomeException → Maybe (ChainDbError blk) # displayException ∷ ChainDbError blk → String # | |
(Typeable blk, StandardHash blk) ⇒ Show (ChainDbError blk) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API showsPrec ∷ Int → ChainDbError blk → ShowS # show ∷ ChainDbError blk → String # showList ∷ [ChainDbError blk] → ShowS # |
Genesis
type GetLoEFragment m blk = m (LoE (AnchoredFragment (Header blk))) Source #
Get the current LoE fragment (if the LoE is enabled), see LoE
for more
details. This fragment must be anchored in a (recent) point on the immutable
chain, just like candidate fragments.
The Limit on Eagerness (LoE) is a mechanism for keeping ChainSel from advancing the current selection in the case of competing chains.
The LoE tip is the youngest header that is present on all candidate fragments. Thus, after the LoE tip, peers either disagree on how the chain follows, or they do not offer more headers.
The LoE restrains the current selection of the node to be on the same chain as the LoE tip, and to not extend more than k blocks from it.
It requires a resolution mechanism to prevent indefinite stalling, which is implemented by the Genesis Density Disconnection governor, a component that disconnects from peers with forks it considers inferior. See Ouroboros.Consensus.Genesis.Governor for details.
This type indicates whether LoE is enabled, and contains a value if it is.
There is no a priori meaning assigned to the type parameter a
.
LoE a
is isomorphic to Maybe a
, with the added meaning that
Just/LoEEnabled
is only used when the LoE is enabled.
LoEDisabled | The LoE is disabled, so ChainSel will not keep the selection from advancing. |
LoEEnabled !a | The LoE is enabled. |
Instances
Foldable LoE Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API foldMap ∷ Monoid m ⇒ (a → m) → LoE a → m # foldMap' ∷ Monoid m ⇒ (a → m) → LoE a → m # foldr ∷ (a → b → b) → b → LoE a → b # foldr' ∷ (a → b → b) → b → LoE a → b # foldl ∷ (b → a → b) → b → LoE a → b # foldl' ∷ (b → a → b) → b → LoE a → b # foldr1 ∷ (a → a → a) → LoE a → a # foldl1 ∷ (a → a → a) → LoE a → a # | |
Traversable LoE Source # | |
Functor LoE Source # | |
Generic (LoE a) Source # | |
Show a ⇒ Show (LoE a) Source # | |
Eq a ⇒ Eq (LoE a) Source # | |
NoThunks a ⇒ NoThunks (LoE a) Source # | |
type Rep (LoE a) Source # | |
Defined in Ouroboros.Consensus.Storage.ChainDB.API type Rep (LoE a) = D1 ('MetaData "LoE" "Ouroboros.Consensus.Storage.ChainDB.API" "ouroboros-consensus-0.21.0.0-inplace" 'False) (C1 ('MetaCons "LoEDisabled" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "LoEEnabled" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) |