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

Ouroboros.Consensus.Util

Description

Miscellaneous utilities

Synopsis

Type-level utility

class Empty a Source #

Instances

Instances details
Empty (a ∷ k) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

class ShowProxy (p ∷ k) where Source #

Minimal complete definition

Nothing

Methods

showProxyProxy p → String Source #

Instances

Instances details
ShowProxy SlotNo 
Instance details

Defined in Ouroboros.Network.Util.ShowProxy

ShowProxy NodeId Source # 
Instance details

Defined in Ouroboros.Consensus.NodeId

ShowProxy Int 
Instance details

Defined in Ouroboros.Network.Util.ShowProxy

Methods

showProxyProxy IntString Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Typeable xs ⇒ ShowProxy (HardForkApplyTxErr 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

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

ShowProxy blk ⇒ ShowProxy (SerialisedHeader blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualBlock m a) → String Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualGenTxErr m a) → String Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

ShowProxy block ⇒ ShowProxy (Point block ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showProxyProxy (Point block) → String Source #

ShowProxy a ⇒ ShowProxy (Serialised a ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

ShowProxy b ⇒ ShowProxy (Tip b ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showProxyProxy (Tip b) → String Source #

ShowProxy block ⇒ ShowProxy (BlockFetch block point ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

Methods

showProxyProxy (BlockFetch block point) → String Source #

(ShowProxy tx, ShowProxy reject) ⇒ ShowProxy (LocalTxSubmission tx reject ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

Methods

showProxyProxy (LocalTxSubmission tx reject) → String Source #

(ShowProxy txid, ShowProxy tx) ⇒ ShowProxy (TxSubmission2 txid tx ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.TxSubmission2.Type

Methods

showProxyProxy (TxSubmission2 txid tx) → String Source #

(ShowProxy block, ShowProxy query) ⇒ ShowProxy (LocalStateQuery block point query ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type

Methods

showProxyProxy (LocalStateQuery block point query) → String Source #

(ShowProxy header, ShowProxy tip) ⇒ ShowProxy (ChainSync header point tip ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.ChainSync.Type

Methods

showProxyProxy (ChainSync header point tip) → String Source #

(ShowProxy txid, ShowProxy tx, ShowProxy slot) ⇒ ShowProxy (LocalTxMonitor txid tx slot ∷ Type) 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Methods

showProxyProxy (LocalTxMonitor txid tx slot) → String Source #

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

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

ShowProxy (BlockQuery blk) ⇒ ShowProxy (Query blk ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

showProxyProxy (Query blk) → String Source #

ShowProxy ('StIdleTxSubmission2 txid tx) 
Instance details

Defined in Ouroboros.Network.Protocol.TxSubmission2.Type

data Some (f ∷ k → Type) where Source #

Constructors

Some ∷ ∀ {k} (f ∷ k → Type) (a ∷ k). f a → Some f 

data SomePair (f ∷ k → Type) (g ∷ k → Type) where Source #

Pair of functors instantiated to the same existential

Constructors

SomePair ∷ f a → g a → SomePair f g 

data SomeSecond f a where Source #

Hide the second type argument of some functor

SomeSecond f a is isomorphic to Some (f a), but is more convenient in partial applications.

Constructors

SomeSecond ∷ !(f a b) → SomeSecond f a 

Instances

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

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

Inject (SomeSecond BlockQuery) Source # 
Instance details

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

Methods

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

Isomorphic (SomeSecond (NestedCtxt f)) Source # 
Instance details

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

HasNestedContent f blk ⇒ Show (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntSomeSecond (NestedCtxt f) blk → ShowS #

showSomeSecond (NestedCtxt f) blk → String #

showList ∷ [SomeSecond (NestedCtxt f) blk] → ShowS #

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

Defined in Ouroboros.Consensus.Ledger.Query

Show (SomeSecond BlockQuery blk) ⇒ Show (SomeSecond Query blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

showsPrecIntSomeSecond Query blk → ShowS #

showSomeSecond Query blk → String #

showList ∷ [SomeSecond Query blk] → ShowS #

SameDepIndex (NestedCtxt_ blk f) ⇒ Eq (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

(==)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

(/=)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

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

Defined in Ouroboros.Consensus.Ledger.Query

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

Defined in Ouroboros.Consensus.Ledger.Query

Methods

(==)SomeSecond Query blk → SomeSecond Query blk → Bool #

(/=)SomeSecond Query blk → SomeSecond Query blk → Bool #

(Typeable f, Typeable blk) ⇒ NoThunks (SomeSecond (NestedCtxt f) blk) Source #

We can write a manual instance using the following quantified constraint:

forall a. NoThunks (f blk a)

However, this constraint would have to be propagated all the way up, which is rather verbose and annoying (standalone deriving has to be used), hence we use InspectHeap for convenience.

Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Folding variations

foldlM' ∷ ∀ m a b. Monad m ⇒ (b → a → m b) → b → [a] → m b Source #

nTimes ∷ ∀ a. (a → a) → Word64 → a → a Source #

Apply a function n times. The value of each application is forced.

nTimesM ∷ ∀ m a. Monad m ⇒ (a → m a) → Word64 → a → m a Source #

Apply a function n times through a monadic bind. The value of each application is forced.

repeatedly ∷ (a → b → b) → [a] → b → b Source #

repeatedlyMMonad m ⇒ (a → b → m b) → [a] → b → m b Source #

Lists

allEqualEq a ⇒ [a] → Bool Source #

chunksInt → [a] → [[a]] Source #

dropLastWord64 → [a] → [a] Source #

Drop the last n elements

firstJust ∷ ∀ a b f. Foldable f ⇒ (a → Maybe b) → f a → Maybe b Source #

markLast ∷ [a] → [Either a a] Source #

Mark the last element of the list as Right

pickOne ∷ [a] → [([a], a, [a])] Source #

All possible ways to pick on element from a list, preserving order

pickOne [1,2,3] = [ ([], 1, [2, 3])
                  , ([1], 2, [3])
                  , ([1,2], 3, [])
                  ]

split ∷ (a → Bool) → [a] → NonEmpty [a] Source #

Split a list given a delimiter predicate.

>>> split (`elem` "xy") "axbyxc"
"a" :| ["b","","c"]

We have the laws

concat (split p as) === filter (not . p) as
length (split p as) === length (filter p as) + 1

splits ∷ [a] → [([a], a, [a])] Source #

Focus on one element in the list

E.g.

   splits [1..3]
== [ ([]    , 1 , [2,3])
   , ([1]   , 2 , [3]  )
   , ([1,2] , 3 , []   )
   ]

takeLastWord64 → [a] → [a] Source #

Take the last n elements

takeUntil ∷ (a → Bool) → [a] → [a] Source #

Take items until the condition is true. If the condition is true for an item, include that item as the last item in the returned list. If the condition was never true, the original list is returned.

takeUntil (== 3) [1,2,3,4]
1,2,3
> takeUntil (== 2) [0,1,0]
0,1,0
> takeUntil (== 2) [2,2,3]
2

Safe variants of existing base functions

lastMaybe ∷ [a] → Maybe a Source #

safeMaximumOrd a ⇒ [a] → Maybe a Source #

safeMaximumBy ∷ (a → a → Ordering) → [a] → Maybe a Source #

safeMaximumOnOrd b ⇒ (a → b) → [a] → Maybe a Source #

Hashes

hashFromBytesE ∷ ∀ h a. (HashAlgorithm h, HasCallStack) ⇒ ByteStringHash h a Source #

Calls hashFromBytes and throws an error if the input is of the wrong length.

hashFromBytesShortE ∷ ∀ h a. (HashAlgorithm h, HasCallStack) ⇒ ShortByteStringHash h a Source #

Calls hashFromBytesShort and throws an error if the input is of the wrong length.

Bytestrings

Monadic utilities

whenJustApplicative f ⇒ Maybe a → (a → f ()) → f () Source #

Test code

checkThat ∷ (Show a, Monad m) ⇒ String → (a → Bool) → a → m () Source #

Assertion

Variation on assert for use in testing code.

Sets

allDisjoint ∷ ∀ a. Ord a ⇒ [Set a] → Bool Source #

Check that a bunch of sets are all mutually disjoint

Composition

(......:) ∷ (y → z) → (x0 → x1 → x2 → x3 → x4 → x5 → x6 → y) → x0 → x1 → x2 → x3 → x4 → x5 → x6 → z Source #

(.....:) ∷ (y → z) → (x0 → x1 → x2 → x3 → x4 → x5 → y) → x0 → x1 → x2 → x3 → x4 → x5 → z Source #

(....:) ∷ (y → z) → (x0 → x1 → x2 → x3 → x4 → y) → x0 → x1 → x2 → x3 → x4 → z Source #

(...:) ∷ (y → z) → (x0 → x1 → x2 → x3 → y) → x0 → x1 → x2 → x3 → z Source #

(..:) ∷ (y → z) → (x0 → x1 → x2 → y) → x0 → x1 → x2 → z Source #

(.:) ∷ (y → z) → (x0 → x1 → y) → x0 → x1 → z Source #

Product

pairFstProduct f g a → f a Source #

pairSndProduct f g a → g a Source #

Miscellaneous

fibWord64Word64 Source #

Fast Fibonacci computation, using Binet's formula

Electric code

data Electric m a Source #

An action that cannot be ran without drawing current through a Fuse.

NOTE: using Fuse m -> ... would suffice but the newtype wrapper is useful for ensuring we don't make mistakes.

Instances

Instances details
MonadTrans (Electric ∷ (TypeType) → TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

liftMonad m ⇒ m a → Electric m a #

Applicative m ⇒ Applicative (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

pure ∷ a → Electric m a #

(<*>)Electric m (a → b) → Electric m a → Electric m b #

liftA2 ∷ (a → b → c) → Electric m a → Electric m b → Electric m c #

(*>)Electric m a → Electric m b → Electric m b #

(<*)Electric m a → Electric m b → Electric m a #

Functor m ⇒ Functor (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

fmap ∷ (a → b) → Electric m a → Electric m b #

(<$) ∷ a → Electric m b → Electric m a #

Monad m ⇒ Monad (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

(>>=)Electric m a → (a → Electric m b) → Electric m b #

(>>)Electric m a → Electric m b → Electric m b #

return ∷ a → Electric m a #

MonadCatch m ⇒ MonadCatch (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

catchException e ⇒ Electric m a → (e → Electric m a) → Electric m a Source #

catchJustException e ⇒ (e → Maybe b) → Electric m a → (b → Electric m a) → Electric m a Source #

tryException e ⇒ Electric m a → Electric m (Either e a) Source #

tryJustException e ⇒ (e → Maybe b) → Electric m a → Electric m (Either b a) Source #

handleException e ⇒ (e → Electric m a) → Electric m a → Electric m a Source #

handleJustException e ⇒ (e → Maybe b) → (b → Electric m a) → Electric m a → Electric m a Source #

onExceptionElectric m a → Electric m b → Electric m a Source #

bracketOnErrorElectric m a → (a → Electric m b) → (a → Electric m c) → Electric m c Source #

generalBracketElectric m a → (a → ExitCase b → Electric m c) → (a → Electric m b) → Electric m (b, c) Source #

MonadThrow m ⇒ MonadThrow (Electric m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Methods

throwIOException e ⇒ e → Electric m a Source #

bracketElectric m a → (a → Electric m b) → (a → Electric m c) → Electric m c Source #

bracket_Electric m a → Electric m b → Electric m c → Electric m c Source #

finallyElectric m a → Electric m b → Electric m a Source #

data Fuse m Source #

A simple semaphore, though instead of blocking a fatal exception is thrown.

Instances

Instances details
Generic (Fuse m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

Associated Types

type Rep (Fuse m) ∷ TypeType #

Methods

fromFuse m → Rep (Fuse m) x #

toRep (Fuse m) x → Fuse m #

NoThunks (StrictMVar m ()) ⇒ NoThunks (Fuse m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

type Rep (Fuse m) Source # 
Instance details

Defined in Ouroboros.Consensus.Util

type Rep (Fuse m) = D1 ('MetaData "Fuse" "Ouroboros.Consensus.Util" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "Fuse" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMVar m ()))))

electric ∷ m a → Electric m a Source #

newFuseMonadMVar m ⇒ String → m (Fuse m) Source #

withFuse ∷ (MonadThrow m, MonadMVar m) ⇒ Fuse m → Electric m a → m a Source #

Put full load on the Fuse while the Electric is running.

Thus any two withFuse calls with the same Fuse will throw one fatal exception.

NOTE The metaphor is: when I run at most one waffle iron concurrently, my kitchen's fuse doesn't blow. But it blows if I run more than one waffle iron concurrently.

WARNING If the given action throws its own exception, then it will never stop putting load on the Fuse.