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

Ouroboros.Consensus.Util

Description

Miscellaneous utilities

Synopsis

Type-level utility

data Dict :: Constraint -> Type where Source #

Constructors

Dict :: a => Dict a

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

Instances

Instances details
Typeable xs => ShowProxy ( Header ( HardForkBlock xs) :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

( 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

( Typeable m, Typeable a) => ShowProxy ( DualHeader m a :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ShowProxy Int
Instance details

Defined in Ouroboros.Network.Util.ShowProxy

ShowProxy SlotNo Source #
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

ShowProxy KeepAlive
Instance details

Defined in Ouroboros.Network.Protocol.KeepAlive.Type

ShowProxy block => ShowProxy ( Point block :: Type )
Instance details

Defined in Ouroboros.Network.Block

ShowProxy b => ShowProxy ( Tip b :: Type )
Instance details

Defined in Ouroboros.Network.Block

ShowProxy a => ShowProxy ( Serialised a :: Type )
Instance details

Defined in Ouroboros.Network.Block

ShowProxy blk => ShowProxy ( SerialisedHeader blk :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

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 m, Typeable a) => ShowProxy ( DualGenTxErr m a :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

( ShowProxy txid, ShowProxy tx) => ShowProxy ( TxSubmission2 txid tx :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.TxSubmission2.Type

( ShowProxy tx, ShowProxy reject) => ShowProxy ( LocalTxSubmission tx reject :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

ShowProxy block => ShowProxy ( BlockFetch block point :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.BlockFetch.Type

ShowProxy ( Handshake vNumber vParams :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.Handshake.Type

( ShowProxy block, ShowProxy query) => ShowProxy ( LocalStateQuery block point query :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.LocalStateQuery.Type

( ShowProxy txid, ShowProxy tx, ShowProxy slot) => ShowProxy ( LocalTxMonitor txid tx slot :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

( ShowProxy header, ShowProxy tip) => ShowProxy ( ChainSync header point tip :: Type )
Instance details

Defined in Ouroboros.Network.Protocol.ChainSync.Type

( 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

ShowProxy ( BlockQuery blk) => ShowProxy ( Query blk :: Type -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

ShowProxy (' StIdle :: TxSubmission2 txid tx)
Instance details

Defined in Ouroboros.Network.Protocol.TxSubmission2.Type

data Some (f :: k -> Type ) where Source #

Constructors

Some :: 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 :: Type -> Type -> Type ) 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
Isomorphic ( SomeSecond ( NestedCtxt f)) Source #
Instance details

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

Inject ( SomeSecond BlockQuery ) Source #
Instance details

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

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

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

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

Defined in Ouroboros.Consensus.Block.NestedContent

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

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

Defined in Ouroboros.Consensus.Block.NestedContent

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

( 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' :: forall m a b. Monad m => (b -> a -> m b) -> b -> [a] -> m b Source #

nTimes :: forall a. (a -> a) -> Word64 -> a -> a Source #

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

nTimesM :: forall 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 #

repeatedlyM :: Monad m => (a -> b -> m b) -> [a] -> b -> m b Source #

Lists

chunks :: Int -> [a] -> [[a]] Source #

dropLast :: Word64 -> [a] -> [a] Source #

Drop the last n elements

firstJust :: forall a b f. Foldable f => (a -> Maybe b) -> f a -> Maybe b Source #

groupOn :: forall a b. Eq b => (a -> b) -> [a] -> [(b, [a])] Source #

Variation on groupBy that records the matched element

   groupOn signum [-3..3]
== [ (-1, [-3, -2,-1])
   , ( 0, [0])
   , ( 1, [1, 2, 3])
   ]

groupSplit :: forall a b c. Eq b => (a -> (b, c)) -> [a] -> [(b, [c])] Source #

Generalization of groupOn where we specify both what to compare and what to collect

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, [])
                  ]

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 , []   )
   ]

takeLast :: Word64 -> [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

Hashes

hashFromBytesE :: forall h a. ( HashAlgorithm h, HasCallStack ) => ByteString -> Hash h a Source #

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

hashFromBytesShortE :: forall h a. ( HashAlgorithm h, HasCallStack ) => ShortByteString -> Hash h a Source #

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

Bytestrings

Monadic utilities

whenJust :: Applicative 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 :: forall 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

Miscellaneous

fib :: Word64 -> Word64 Source #

Fast Fibonacci computation, using Binet's formula