ouroboros-consensus-0.26.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Ledger.Tables.Combinators

Description

Ledger tables are barbie-types (see barbies package), though unfortunately we can not implement classes like FunctorB for ledger tables because the class expects a type that is indexed over a (uni-)functor. Ledger tables are indexed over bifunctors (mapkinds), so the kinds do not match. To cut on boilerplate, we do not define variants of FunctorB (and similar classes) for types that are indexed over bifunctors. Instead, we define specialised variants of class functions and utility functions. For example:

TODO: if we make mapkinds of kind (k1, k2) -> Type instead of k1 -> k2 -> Type, then we could reuse most of the barbies machinery.

Synopsis

Common constraints

type LedgerTableConstraints (l ∷ LedgerStateKind) = (Ord (TxIn l), Eq (TxOut l), MemPack (TxIn l), IndexedMemPack (MemPackIdx l EmptyMK) (TxOut l)) Source #

The Eq (TxOut l) constraint is here only because of diff. Once the ledger provides deltas instead of us being the ones that compute them, we can probably drop this constraint.

Functor

ltmap ∷ ∀ (l ∷ LedgerStateKind) mk1 mk2. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v) → LedgerTables l mk1 → LedgerTables l mk2 Source #

Like bmap, but for ledger tables.

Traversable

lttraverse ∷ ∀ f (l ∷ LedgerStateKind) mk1 mk2. (Applicative f, LedgerTableConstraints l) ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → f (mk2 k v)) → LedgerTables l mk1 → f (LedgerTables l mk2) Source #

Like btraverse, but for ledger tables.

Utility functions

ltsequence ∷ ∀ f (l ∷ LedgerStateKind) (mk ∷ TypeTypeType). (Applicative f, LedgerTableConstraints l) ⇒ LedgerTables l (f :..: mk) → f (LedgerTables l mk) Source #

Applicative

ltprod ∷ ∀ (l ∷ LedgerStateKind) (f ∷ MapKind) (g ∷ MapKind). LedgerTables l f → LedgerTables l g → LedgerTables l (Product2 f g) Source #

Like bprod, but for ledger tables.

ltpure ∷ ∀ (l ∷ LedgerStateKind) mk. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk k v) → LedgerTables l mk Source #

Like bpure, but for ledger tables.

Utility functions

ltap ∷ ∀ (l ∷ LedgerStateKind) (mk1 ∷ TypeTypeType) (mk2 ∷ TypeTypeType). LedgerTableConstraints l ⇒ LedgerTables l (mk1 -..-> mk2) → LedgerTables l mk1 → LedgerTables l mk2 Source #

ltliftA ∷ ∀ (l ∷ LedgerStateKind) mk1 mk2. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v) → LedgerTables l mk1 → LedgerTables l mk2 Source #

ltliftA2 ∷ ∀ (l ∷ LedgerStateKind) mk1 mk2 mk3. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v → mk3 k v) → LedgerTables l mk1 → LedgerTables l mk2 → LedgerTables l mk3 Source #

ltliftA3 ∷ ∀ (l ∷ LedgerStateKind) mk1 mk2 mk3 mk4. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v → mk3 k v → mk4 k v) → LedgerTables l mk1 → LedgerTables l mk2 → LedgerTables l mk3 → LedgerTables l mk4 Source #

ltliftA4 ∷ ∀ (l ∷ LedgerStateKind) mk1 mk2 mk3 mk4 mk5. LedgerTableConstraints l ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v → mk3 k v → mk4 k v → mk5 k v) → LedgerTables l mk1 → LedgerTables l mk2 → LedgerTables l mk3 → LedgerTables l mk4 → LedgerTables l mk5 Source #

Applicative and Traversable

ltzipWith2A ∷ ∀ f (l ∷ LedgerStateKind) mk1 mk2 mk3. (Applicative f, LedgerTableConstraints l) ⇒ (∀ k v. LedgerTableConstraints' l k v ⇒ mk1 k v → mk2 k v → f (mk3 k v)) → LedgerTables l mk1 → LedgerTables l mk2 → f (LedgerTables l mk3) Source #

Collapsing

ltcollapse ∷ ∀ (l ∷ LedgerStateKind) a. LedgerTables l (K2 a ∷ TypeTypeType) → a Source #

Lifted functions

fn2_1 ∷ ∀ {k1} {k2} f (a ∷ k1) (b ∷ k2) g. (f a b → g a b) → (f -..-> g) a b Source #

Construct a lifted function.

fn2_2 ∷ ∀ {k1} {k2} f (a ∷ k1) (b ∷ k2) f' f''. (f a b → f' a b → f'' a b) → (f -..-> (f' -..-> f'')) a b Source #

Construct a binary lifted function

fn2_3 ∷ ∀ {k1} {k2} f (a ∷ k1) (b ∷ k2) f' f'' f'''. (f a b → f' a b → f'' a b → f''' a b) → (f -..-> (f' -..-> (f'' -..-> f'''))) a b Source #

Construct a ternary lifted function.

fn2_4 ∷ ∀ {k1} {k2} f (a ∷ k1) (b ∷ k2) f' f'' f''' f''''. (f a b → f' a b → f'' a b → f''' a b → f'''' a b) → (f -..-> (f' -..-> (f'' -..-> (f''' -..-> f'''')))) a b Source #

Construct a quaternary lifted function.

newtype ((f ∷ k1 → k2 → Type) -..-> (g ∷ k1 → k2 → Type)) (a ∷ k1) (b ∷ k2) infixr 1 Source #

Lifted functions

Similar to (-.->), but for f and g that are bifunctors.

Constructors

Fn2 

Fields

  • apFn2 ∷ f a b → g a b
     

Re-exports of utils

(...:) ∷ (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 #

Basic bifunctors

newtype K2 a (b ∷ k1) (c ∷ k2) Source #

The constant type bifunctor.

Constructors

K2 

Fields

Instances

Instances details
Bifunctor (K2 a ∷ TypeTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

bimap ∷ (a0 → b) → (c → d) → K2 a a0 c → K2 a b d #

first ∷ (a0 → b) → K2 a a0 c → K2 a b c #

second ∷ (b → c) → K2 a a0 b → K2 a a0 c #

Functor (K2 a b ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

fmap ∷ (a0 → b0) → K2 a b a0 → K2 a b b0 #

(<$) ∷ a0 → K2 a b b0 → K2 a b a0 #

Foldable (K2 a b ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

foldMonoid m ⇒ K2 a b m → m #

foldMapMonoid m ⇒ (a0 → m) → K2 a b a0 → m #

foldMap'Monoid m ⇒ (a0 → m) → K2 a b a0 → m #

foldr ∷ (a0 → b0 → b0) → b0 → K2 a b a0 → b0 #

foldr' ∷ (a0 → b0 → b0) → b0 → K2 a b a0 → b0 #

foldl ∷ (b0 → a0 → b0) → b0 → K2 a b a0 → b0 #

foldl' ∷ (b0 → a0 → b0) → b0 → K2 a b a0 → b0 #

foldr1 ∷ (a0 → a0 → a0) → K2 a b a0 → a0 #

foldl1 ∷ (a0 → a0 → a0) → K2 a b a0 → a0 #

toListK2 a b a0 → [a0] #

nullK2 a b a0 → Bool #

lengthK2 a b a0 → Int #

elemEq a0 ⇒ a0 → K2 a b a0 → Bool #

maximumOrd a0 ⇒ K2 a b a0 → a0 #

minimumOrd a0 ⇒ K2 a b a0 → a0 #

sumNum a0 ⇒ K2 a b a0 → a0 #

productNum a0 ⇒ K2 a b a0 → a0 #

Traversable (K2 a b ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

traverseApplicative f ⇒ (a0 → f b0) → K2 a b a0 → f (K2 a b b0) #

sequenceAApplicative f ⇒ K2 a b (f a0) → f (K2 a b a0) #

mapMMonad m ⇒ (a0 → m b0) → K2 a b a0 → m (K2 a b b0) #

sequenceMonad m ⇒ K2 a b (m a0) → m (K2 a b a0) #

Monoid a ⇒ Monoid (K2 a b c) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

memptyK2 a b c #

mappendK2 a b c → K2 a b c → K2 a b c #

mconcat ∷ [K2 a b c] → K2 a b c #

Semigroup a ⇒ Semigroup (K2 a b c) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

(<>)K2 a b c → K2 a b c → K2 a b c #

sconcatNonEmpty (K2 a b c) → K2 a b c #

stimesIntegral b0 ⇒ b0 → K2 a b c → K2 a b c #

Show a ⇒ Show (K2 a b c) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

showsPrecIntK2 a b c → ShowS #

showK2 a b c → String #

showList ∷ [K2 a b c] → ShowS #

Eq a ⇒ Eq (K2 a b c) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

(==)K2 a b c → K2 a b c → Bool #

(/=)K2 a b c → K2 a b c → Bool #

newtype ((f ∷ k3 → Type) :..: (g ∷ k1 → k2 → k3)) (a ∷ k1) (b ∷ k2) infixr 7 Source #

Composition of functor after bifunctor.

Example: Comp2 (Just (17, True)) :: (Maybe :..: (,)) Int Bool

Constructors

Comp2 

Fields

Instances

Instances details
(Functor f, Bifunctor g) ⇒ Bifunctor (f :..: g) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

bimap ∷ (a → b) → (c → d) → (f :..: g) a c → (f :..: g) b d #

first ∷ (a → b) → (f :..: g) a c → (f :..: g) b c #

second ∷ (b → c) → (f :..: g) a b → (f :..: g) a c #

(Functor f, Functor (g a)) ⇒ Functor ((f :..: g) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

fmap ∷ (a0 → b) → (f :..: g) a a0 → (f :..: g) a b #

(<$) ∷ a0 → (f :..: g) a b → (f :..: g) a a0 #

(Foldable f, Foldable (g a)) ⇒ Foldable ((f :..: g) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

foldMonoid m ⇒ (f :..: g) a m → m #

foldMapMonoid m ⇒ (a0 → m) → (f :..: g) a a0 → m #

foldMap'Monoid m ⇒ (a0 → m) → (f :..: g) a a0 → m #

foldr ∷ (a0 → b → b) → b → (f :..: g) a a0 → b #

foldr' ∷ (a0 → b → b) → b → (f :..: g) a a0 → b #

foldl ∷ (b → a0 → b) → b → (f :..: g) a a0 → b #

foldl' ∷ (b → a0 → b) → b → (f :..: g) a a0 → b #

foldr1 ∷ (a0 → a0 → a0) → (f :..: g) a a0 → a0 #

foldl1 ∷ (a0 → a0 → a0) → (f :..: g) a a0 → a0 #

toList ∷ (f :..: g) a a0 → [a0] #

null ∷ (f :..: g) a a0 → Bool #

length ∷ (f :..: g) a a0 → Int #

elemEq a0 ⇒ a0 → (f :..: g) a a0 → Bool #

maximumOrd a0 ⇒ (f :..: g) a a0 → a0 #

minimumOrd a0 ⇒ (f :..: g) a a0 → a0 #

sumNum a0 ⇒ (f :..: g) a a0 → a0 #

productNum a0 ⇒ (f :..: g) a a0 → a0 #

(Traversable f, Traversable (g a)) ⇒ Traversable ((f :..: g) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

traverseApplicative f0 ⇒ (a0 → f0 b) → (f :..: g) a a0 → f0 ((f :..: g) a b) #

sequenceAApplicative f0 ⇒ (f :..: g) a (f0 a0) → f0 ((f :..: g) a a0) #

mapMMonad m ⇒ (a0 → m b) → (f :..: g) a a0 → m ((f :..: g) a b) #

sequenceMonad m ⇒ (f :..: g) a (m a0) → m ((f :..: g) a a0) #

Monoid (f (g a b)) ⇒ Monoid ((f :..: g) a b) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

mempty ∷ (f :..: g) a b #

mappend ∷ (f :..: g) a b → (f :..: g) a b → (f :..: g) a b #

mconcat ∷ [(f :..: g) a b] → (f :..: g) a b #

Semigroup (f (g a b)) ⇒ Semigroup ((f :..: g) a b) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

(<>) ∷ (f :..: g) a b → (f :..: g) a b → (f :..: g) a b #

sconcatNonEmpty ((f :..: g) a b) → (f :..: g) a b #

stimesIntegral b0 ⇒ b0 → (f :..: g) a b → (f :..: g) a b #

Show (f (g a b)) ⇒ Show ((f :..: g) a b) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

showsPrecInt → (f :..: g) a b → ShowS #

show ∷ (f :..: g) a b → String #

showList ∷ [(f :..: g) a b] → ShowS #

Eq (f (g a b)) ⇒ Eq ((f :..: g) a b) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Combinators

Methods

(==) ∷ (f :..: g) a b → (f :..: g) a b → Bool #

(/=) ∷ (f :..: g) a b → (f :..: g) a b → Bool #

Orphan instances

(∀ k v. LedgerTableConstraints' l k v ⇒ Monoid (mk k v), LedgerTableConstraints l) ⇒ Monoid (LedgerTables l mk) Source # 
Instance details

Methods

memptyLedgerTables l mk #

mappendLedgerTables l mk → LedgerTables l mk → LedgerTables l mk #

mconcat ∷ [LedgerTables l mk] → LedgerTables l mk #

(∀ k v. LedgerTableConstraints' l k v ⇒ Semigroup (mk k v), LedgerTableConstraints l) ⇒ Semigroup (LedgerTables l mk) Source # 
Instance details

Methods

(<>)LedgerTables l mk → LedgerTables l mk → LedgerTables l mk #

sconcatNonEmpty (LedgerTables l mk) → LedgerTables l mk #

stimesIntegral b ⇒ b → LedgerTables l mk → LedgerTables l mk #