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

Ouroboros.Consensus.Storage.VolatileDB.Impl.State

Synopsis

Tracing

data TraceEvent blk Source #

Instances

Instances details
Generic (TraceEvent blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep (TraceEvent blk) ∷ TypeType #

Methods

fromTraceEvent blk → Rep (TraceEvent blk) x #

toRep (TraceEvent blk) x → TraceEvent blk #

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

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Methods

showsPrecIntTraceEvent blk → ShowS #

showTraceEvent blk → String #

showList ∷ [TraceEvent blk] → ShowS #

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

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Methods

(==)TraceEvent blk → TraceEvent blk → Bool #

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

type Rep (TraceEvent blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

type Rep (TraceEvent blk) = D1 ('MetaData "TraceEvent" "Ouroboros.Consensus.Storage.VolatileDB.Impl.Types" "ouroboros-consensus-0.18.0.0-inplace" 'False) ((C1 ('MetaCons "DBAlreadyClosed" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "BlockAlreadyHere" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash blk)))) :+: (C1 ('MetaCons "Truncate" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ParseError blk)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FsPath) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockOffset))) :+: (C1 ('MetaCons "InvalidFileNames" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FsPath])) :+: C1 ('MetaCons "DBClosed" 'PrefixI 'False) (U1TypeType))))

State types

newtype BlockOffset Source #

The offset at which a block is stored in a file.

Constructors

BlockOffset 

Fields

Instances

Instances details
Generic BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep BlockOffsetTypeType #

Show BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Eq BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

NoThunks BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

type Rep BlockOffset Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

type Rep BlockOffset = D1 ('MetaData "BlockOffset" "Ouroboros.Consensus.Storage.VolatileDB.Impl.Types" "ouroboros-consensus-0.18.0.0-inplace" 'True) (C1 ('MetaCons "BlockOffset" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype BlockSize Source #

Constructors

BlockSize 

Fields

Instances

Instances details
Generic BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Associated Types

type Rep BlockSizeTypeType #

Methods

fromBlockSizeRep BlockSize x #

toRep BlockSize x → BlockSize #

Show BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Methods

showsPrecIntBlockSizeShowS #

showBlockSizeString #

showList ∷ [BlockSize] → ShowS #

Eq BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

Methods

(==)BlockSizeBlockSizeBool #

(/=)BlockSizeBlockSizeBool #

NoThunks BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

type Rep BlockSize Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.Types

type Rep BlockSize = D1 ('MetaData "BlockSize" "Ouroboros.Consensus.Storage.VolatileDB.Impl.Types" "ouroboros-consensus-0.18.0.0-inplace" 'True) (C1 ('MetaCons "BlockSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

type FileId = Int Source #

The FileId is the unique identifier of each file found in the db. For example, the file blocks-42.dat has FileId 42.

data InternalState blk h Source #

Constructors

DbClosed 
DbOpen !(OpenState blk h) 

Instances

Instances details
Generic (InternalState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

Associated Types

type Rep (InternalState blk h) ∷ TypeType #

Methods

fromInternalState blk h → Rep (InternalState blk h) x #

toRep (InternalState blk h) x → InternalState blk h #

(StandardHash blk, Typeable blk) ⇒ NoThunks (InternalState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

type Rep (InternalState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

type Rep (InternalState blk h) = D1 ('MetaData "InternalState" "Ouroboros.Consensus.Storage.VolatileDB.Impl.State" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "DbClosed" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "DbOpen" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OpenState blk h))))

data OpenState blk h Source #

Internal state when the database is open.

Constructors

OpenState 

Fields

Instances

Instances details
Generic (OpenState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

Associated Types

type Rep (OpenState blk h) ∷ TypeType #

Methods

fromOpenState blk h → Rep (OpenState blk h) x #

toRep (OpenState blk h) x → OpenState blk h #

(StandardHash blk, Typeable blk) ⇒ NoThunks (OpenState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

type Rep (OpenState blk h) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.VolatileDB.Impl.State

type Rep (OpenState blk h) = D1 ('MetaData "OpenState" "Ouroboros.Consensus.Storage.VolatileDB.Impl.State" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "OpenState" 'PrefixI 'True) (((S1 ('MetaSel ('Just "currentWriteHandle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Handle h)) :*: S1 ('MetaSel ('Just "currentWritePath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FsPath)) :*: (S1 ('MetaSel ('Just "currentWriteId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FileId) :*: S1 ('MetaSel ('Just "currentWriteOffset") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "currentMap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Index blk)) :*: S1 ('MetaSel ('Just "currentRevMap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ReverseIndex blk))) :*: (S1 ('MetaSel ('Just "currentSuccMap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SuccessorsIndex blk)) :*: S1 ('MetaSel ('Just "currentMaxSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MaxSlotNo)))))

type ReverseIndex blk = Map (HeaderHash blk) (InternalBlockInfo blk) Source #

We map the header hash of each block to the InternalBlockInfo.

type SuccessorsIndex blk = Map (ChainHash blk) (Set (HeaderHash blk)) Source #

For each block, we store the set of all blocks which have this block as a predecessor (set of successors).

data VolatileDBEnv m blk Source #

Constructors

∀ h.Eq h ⇒ VolatileDBEnv 

Fields

State helpers

type ModifyOpenState m blk h = StateT (OpenState blk h) (WithTempRegistry (OpenState blk h) m) Source #

Shorthand

appendOpenState ∷ ∀ blk m a. (IOLike m, Typeable blk, StandardHash blk) ⇒ VolatileDBEnv m blk → (∀ h. Eq h ⇒ HasFS m h → ModifyOpenState m blk h a) → m a Source #

Append to the open state. Reads can happen concurrently with this operation.

NOTE: This is safe in terms of throwing FsErrors.

closeOpenHandlesHasFS m h → OpenState blk h → m () Source #

Close the handles in the OpenState.

Idempotent, as closing a handle is idempotent.

NOTE: does not wrap FsErrors and must be called within wrapFsError or tryVolatileDB.

mkOpenState ∷ ∀ m blk h. (HasCallStack, IOLike m, GetPrevHash blk, HasBinaryBlockInfo blk, HasNestedContent Header blk, DecodeDisk blk (ByteString → blk), Eq h) ⇒ CodecConfig blk → HasFS m h → (blk → Bool) → BlockValidationPolicyTracer m (TraceEvent blk) → BlocksPerFileWithTempRegistry (OpenState blk h) m (OpenState blk h) Source #

withOpenState ∷ ∀ blk m r. (IOLike m, StandardHash blk, Typeable blk) ⇒ VolatileDBEnv m blk → (∀ h. HasFS m h → OpenState blk h → m r) → m r Source #

Perform an action that accesses the internal state of an open database.

In case the database is closed, a ClosedDBError is thrown.

In case an VolatileDBError is thrown while the action is being run, the database is closed to prevent further appending to a database in a potentially inconsistent state. All other exceptions will leave the database open.

writeOpenState ∷ ∀ blk m a. (IOLike m, Typeable blk, StandardHash blk) ⇒ VolatileDBEnv m blk → (∀ h. Eq h ⇒ HasFS m h → ModifyOpenState m blk h a) → m a Source #

Write to the open state. No reads or appends can concurrently with this operation.

NOTE: This is safe in terms of throwing FsErrors.