ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Storage.ImmutableDB.API

Synopsis

API

data ImmutableDB m blk Source #

API for the ImmutableDB.

The ImmutableDB stores blocks in SlotNos. Nevertheless, lookups use RealPoint, primarily because Epoch Boundary Blocks (EBBs) have the same SlotNo as the regular block after them (unless that slot is empty), so that we have to use the hash of the block to distinguish the two (hence RealPoint). But also to avoid reading the wrong block, i.e., when we expect a block with a different hash.

The database is append-only, so you cannot append a block to a slot in the past. You can, however, skip slots, e.g., append to slot 0 and then to slot 5, but afterwards, you can no longer append to slots 1-4. You can only store at most one block in each slot, except for EBBs, which are stored separately, at the start of each epoch/chunk.

The block stored in a slot can be queried with getBlockComponent. Block components can also be streamed using Iterators, see stream.

The Tip of the database can be queried with getTip. This tip will always point to a filled slot or an EBB that is present.

The database can be explicitly closed, but can also be automatically closed in case of an ImmutableDBError.

Constructors

ImmutableDB 

Fields

Instances

Instances details
NoThunks (ImmutableDB m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Iterator API

data Iterator m blk b Source #

An Iterator is a handle which can be used to efficiently stream block components from the ImmutableDB.

Constructors

Iterator 

Fields

Instances

Instances details
Functor m ⇒ Functor (Iterator m blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

fmap ∷ (a → b) → Iterator m blk a → Iterator m blk b #

(<$) ∷ a → Iterator m blk b → Iterator m blk a #

NoThunks (Iterator m blk b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

noThunksContextIterator m blk b → IO (Maybe ThunkInfo) Source #

wNoThunksContextIterator m blk b → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Iterator m blk b) → String Source #

data IteratorResult b Source #

The result of stepping an Iterator.

Instances

Instances details
Foldable IteratorResult Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

foldMonoid m ⇒ IteratorResult m → m #

foldMapMonoid m ⇒ (a → m) → IteratorResult a → m #

foldMap'Monoid m ⇒ (a → m) → IteratorResult a → m #

foldr ∷ (a → b → b) → b → IteratorResult a → b #

foldr' ∷ (a → b → b) → b → IteratorResult a → b #

foldl ∷ (b → a → b) → b → IteratorResult a → b #

foldl' ∷ (b → a → b) → b → IteratorResult a → b #

foldr1 ∷ (a → a → a) → IteratorResult a → a #

foldl1 ∷ (a → a → a) → IteratorResult a → a #

toListIteratorResult a → [a] #

nullIteratorResult a → Bool #

lengthIteratorResult a → Int #

elemEq a ⇒ a → IteratorResult a → Bool #

maximumOrd a ⇒ IteratorResult a → a #

minimumOrd a ⇒ IteratorResult a → a #

sumNum a ⇒ IteratorResult a → a #

productNum a ⇒ IteratorResult a → a #

Traversable IteratorResult Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

traverseApplicative f ⇒ (a → f b) → IteratorResult a → f (IteratorResult b) #

sequenceAApplicative f ⇒ IteratorResult (f a) → f (IteratorResult a) #

mapMMonad m ⇒ (a → m b) → IteratorResult a → m (IteratorResult b) #

sequenceMonad m ⇒ IteratorResult (m a) → m (IteratorResult a) #

Functor IteratorResult Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

fmap ∷ (a → b) → IteratorResult a → IteratorResult b #

(<$) ∷ a → IteratorResult b → IteratorResult a #

Generic (IteratorResult b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (IteratorResult b) ∷ TypeType #

Methods

fromIteratorResult b → Rep (IteratorResult b) x #

toRep (IteratorResult b) x → IteratorResult b #

Show b ⇒ Show (IteratorResult b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Eq b ⇒ Eq (IteratorResult b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

type Rep (IteratorResult b) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

type Rep (IteratorResult b) = D1 ('MetaData "IteratorResult" "Ouroboros.Consensus.Storage.ImmutableDB.API" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "IteratorExhausted" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "IteratorResult" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

iteratorToList ∷ (HasCallStack, Monad m) ⇒ Iterator m blk b → m [b] Source #

Consume an Iterator by stepping until it is exhausted. A list of all the IteratorResults (excluding the final IteratorExhausted) produced by the Iterator is returned.

traverseIteratorMonad m ⇒ (b → m b') → Iterator m blk b → Iterator m blk b' Source #

Variant of traverse instantiated to Iterator m blk m that executes the monadic function when calling iteratorNext.

Types

newtype CompareTip blk Source #

newtype with an Ord instance that only uses tipSlotNo and tipIsEBB and ignores the other fields.

Constructors

CompareTip 

Fields

Instances

Instances details
Eq (CompareTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

(==)CompareTip blk → CompareTip blk → Bool #

(/=)CompareTip blk → CompareTip blk → Bool #

Ord (CompareTip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

compareCompareTip blk → CompareTip blk → Ordering #

(<)CompareTip blk → CompareTip blk → Bool #

(<=)CompareTip blk → CompareTip blk → Bool #

(>)CompareTip blk → CompareTip blk → Bool #

(>=)CompareTip blk → CompareTip blk → Bool #

maxCompareTip blk → CompareTip blk → CompareTip blk #

minCompareTip blk → CompareTip blk → CompareTip blk #

data Tip blk Source #

Information about the tip of the ImmutableDB.

Constructors

Tip 

Fields

Instances

Instances details
Generic (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (Tip blk) ∷ TypeType #

Methods

fromTip blk → Rep (Tip blk) x #

toRep (Tip blk) x → Tip blk #

StandardHash blk ⇒ Show (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

showsPrecIntTip blk → ShowS #

showTip blk → String #

showList ∷ [Tip blk] → ShowS #

StandardHash blk ⇒ Eq (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

(==)Tip blk → Tip blk → Bool #

(/=)Tip blk → Tip blk → Bool #

StandardHash blk ⇒ NoThunks (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

noThunksContextTip blk → IO (Maybe ThunkInfo) Source #

wNoThunksContextTip blk → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Tip blk) → String Source #

type Rep (Tip blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

type Rep (Tip blk) = D1 ('MetaData "Tip" "Ouroboros.Consensus.Storage.ImmutableDB.API" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "Tip" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tipSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: S1 ('MetaSel ('Just "tipIsEBB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IsEBB)) :*: (S1 ('MetaSel ('Just "tipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "tipHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash blk)))))

blockToTip ∷ (HasHeader blk, GetHeader blk) ⇒ blk → Tip blk Source #

Errors

data ApiMisuse blk Source #

Constructors

AppendBlockNotNewerThanTipError (RealPoint blk) (Point blk)

When trying to append a new block, it was not newer than the current tip, i.e., the slot was older than or equal to the current tip's slot.

The RealPoint corresponds to the new block and the Point to the current tip.

InvalidIteratorRangeError (StreamFrom blk) (StreamTo blk)

When the chosen iterator range was invalid, i.e. the start (first parameter) came after the end (second parameter).

ClosedDBError

When performing an operation on a closed DB that is only allowed when the database is open.

OpenDBError

When performing an operation on an open DB that is only allowed when the database is closed.

Instances

Instances details
(StandardHash blk, Typeable blk) ⇒ Show (ApiMisuse blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

showsPrecIntApiMisuse blk → ShowS #

showApiMisuse blk → String #

showList ∷ [ApiMisuse blk] → ShowS #

data ImmutableDBError blk Source #

Errors that might arise when working with this database.

Constructors

ApiMisuse (ApiMisuse blk) PrettyCallStack

An error thrown because of incorrect usage of the immutable database by the user.

UnexpectedFailure (UnexpectedFailure blk)

An unexpected error thrown because something went wrong on a lower layer.

Instances

Instances details
(StandardHash blk, Typeable blk) ⇒ Exception (ImmutableDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Generic (ImmutableDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (ImmutableDBError blk) ∷ TypeType #

Methods

fromImmutableDBError blk → Rep (ImmutableDBError blk) x #

toRep (ImmutableDBError blk) x → ImmutableDBError blk #

(StandardHash blk, Typeable blk) ⇒ Show (ImmutableDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

type Rep (ImmutableDBError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

type Rep (ImmutableDBError blk) = D1 ('MetaData "ImmutableDBError" "Ouroboros.Consensus.Storage.ImmutableDB.API" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "ApiMisuse" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ApiMisuse blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrettyCallStack)) :+: C1 ('MetaCons "UnexpectedFailure" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UnexpectedFailure blk))))

data MissingBlock blk Source #

This type can be part of an exception, but also returned as part of an Either, because it can be expected in some cases.

Constructors

EmptySlot (RealPoint blk)

There is no block in the slot of the given point.

WrongHash (RealPoint blk) (NonEmpty (HeaderHash blk))

The block and/or EBB in the slot of the given point have a different hash. We return the HeaderHash for each block we found with the corresponding slot number.

NewerThanTip (RealPoint blk) (Point blk)

The requested point is in the future, i.e., its slot is greater than that of the tip. We record the tip as the second argument.

Instances

Instances details
Generic (MissingBlock blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Associated Types

type Rep (MissingBlock blk) ∷ TypeType #

Methods

fromMissingBlock blk → Rep (MissingBlock blk) x #

toRep (MissingBlock blk) x → MissingBlock blk #

StandardHash blk ⇒ Show (MissingBlock blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

showsPrecIntMissingBlock blk → ShowS #

showMissingBlock blk → String #

showList ∷ [MissingBlock blk] → ShowS #

StandardHash blk ⇒ Eq (MissingBlock blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

Methods

(==)MissingBlock blk → MissingBlock blk → Bool #

(/=)MissingBlock blk → MissingBlock blk → Bool #

type Rep (MissingBlock blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

data UnexpectedFailure blk Source #

Constructors

FileSystemError FsError

An IO operation on the file-system threw an error.

InvalidFileError FsPath String PrettyCallStack

When loading an epoch or index file, its contents did not pass validation.

MissingFileError FsPath PrettyCallStack

A missing epoch or index file.

ChecksumMismatchError (RealPoint blk) CRC CRC FsPath PrettyCallStack

There was a checksum mismatch when reading the block with the given point. The first CRC is the expected one, the second one the actual one.

ParseError FsPath (RealPoint blk) DeserialiseFailure

A block failed to parse

TrailingDataError FsPath (RealPoint blk) ByteString

When parsing a block we got some trailing data

MissingBlockError (MissingBlock blk)

Block missing

This exception gets thrown when a block that we know it should be in the ImmutableDB, nonetheless was not found.

CorruptBlockError (RealPoint blk)

A (parsed) block did not pass the integrity check.

This exception gets thrown when a block doesn't pass the integrity check done for GetVerifiedBlock.

NOTE: we do not check the integrity of a block when it is added to the ImmutableDB. While this exception typically means the block has been corrupted, it could also mean the block didn't pass the check at the time it was added.

Instances

Instances details
(StandardHash blk, Typeable blk) ⇒ Show (UnexpectedFailure blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ImmutableDB.API

missingBlockPointMissingBlock blk → RealPoint blk Source #

Return the RealPoint of the block that was missing.

Wrappers that preserve HasCallStack

appendBlockHasCallStackImmutableDB m blk → blk → m () Source #

closeDBHasCallStackImmutableDB m blk → m () Source #

getTipHasCallStackImmutableDB m blk → STM m (WithOrigin (Tip blk)) Source #

streamHasCallStackImmutableDB m blk → ResourceRegistry m → BlockComponent blk b → StreamFrom blk → StreamTo blk → m (Either (MissingBlock blk) (Iterator m blk b)) Source #

Derived functionality

getKnownBlockComponent ∷ (MonadThrow m, HasHeader blk) ⇒ ImmutableDB m blk → BlockComponent blk b → RealPoint blk → m b Source #

getTipPoint ∷ (MonadSTM m, HasCallStack) ⇒ ImmutableDB m blk → STM m (Point blk) Source #

hasBlock ∷ (MonadSTM m, HasCallStack) ⇒ ImmutableDB m blk → RealPoint blk → m Bool Source #

streamAfterKnownPoint ∷ (MonadSTM m, MonadThrow m, HasHeader blk, HasCallStack) ⇒ ImmutableDB m blk → ResourceRegistry m → BlockComponent blk b → Point blk → m (Iterator m blk b) Source #

Variant of streamAfterPoint that throws a MissingBlockError when the point is not in the ImmutableDB (or genesis).

streamAfterPoint ∷ (MonadSTM m, HasHeader blk, HasCallStack) ⇒ ImmutableDB m blk → ResourceRegistry m → BlockComponent blk b → Point blk → m (Either (MissingBlock blk) (Iterator m blk b)) Source #

Open an iterator with the given point as lower exclusive bound and the current tip as the inclusive upper bound.

Returns a MissingBlock when the point is not in the ImmutableDB.

withDB Source #

Arguments

∷ (HasCallStack, MonadThrow m) 
⇒ m (ImmutableDB m blk)

How to open the database

→ (ImmutableDB m blk → m a)

Action to perform using the database

→ m a 

Open the database using the given function, perform the given action using the database, and closes the database using its closeDB function, in case of success or when an exception was raised.