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

Ouroboros.Consensus.Ledger.Basics

Description

Definition is IsLedger

Normally this is imported from Ouroboros.Consensus.Ledger.Abstract. We pull this out to avoid circular module dependencies.

Synopsis

GetTip

class GetTip l where Source #

Methods

getTip ∷ l → Point l Source #

Point of the most recently applied block

Should be GenesisPoint when no blocks have been applied yet

Instances

Instances details
CanHardFork xs ⇒ GetTip (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

IsLedger (LedgerState blk) ⇒ GetTip (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

IsLedger l ⇒ GetTip (LedgerDB l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

Methods

getTipLedgerDB l → Point (LedgerDB l) Source #

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

getTipHashGetTip l ⇒ l → ChainHash l Source #

Ledger Events

data LedgerResult l a Source #

The result of invoke a ledger function that does validation

Note: we do not instantiate Applicative or Monad for this type because those interfaces would typically incur space leaks. We encourage you to process the events each time you invoke a ledger function.

Constructors

LedgerResult 

Fields

Instances

Instances details
Foldable (LedgerResult l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Methods

foldMonoid m ⇒ LedgerResult l m → m #

foldMapMonoid m ⇒ (a → m) → LedgerResult l a → m #

foldMap'Monoid m ⇒ (a → m) → LedgerResult l a → m #

foldr ∷ (a → b → b) → b → LedgerResult l a → b #

foldr' ∷ (a → b → b) → b → LedgerResult l a → b #

foldl ∷ (b → a → b) → b → LedgerResult l a → b #

foldl' ∷ (b → a → b) → b → LedgerResult l a → b #

foldr1 ∷ (a → a → a) → LedgerResult l a → a #

foldl1 ∷ (a → a → a) → LedgerResult l a → a #

toListLedgerResult l a → [a] #

nullLedgerResult l a → Bool #

lengthLedgerResult l a → Int #

elemEq a ⇒ a → LedgerResult l a → Bool #

maximumOrd a ⇒ LedgerResult l a → a #

minimumOrd a ⇒ LedgerResult l a → a #

sumNum a ⇒ LedgerResult l a → a #

productNum a ⇒ LedgerResult l a → a #

Traversable (LedgerResult l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Methods

traverseApplicative f ⇒ (a → f b) → LedgerResult l a → f (LedgerResult l b) #

sequenceAApplicative f ⇒ LedgerResult l (f a) → f (LedgerResult l a) #

mapMMonad m ⇒ (a → m b) → LedgerResult l a → m (LedgerResult l b) #

sequenceMonad m ⇒ LedgerResult l (m a) → m (LedgerResult l a) #

Functor (LedgerResult l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Methods

fmap ∷ (a → b) → LedgerResult l a → LedgerResult l b #

(<$) ∷ a → LedgerResult l b → LedgerResult l a #

data VoidLedgerEvent l Source #

A Void isomorph for explicitly declaring that some ledger has no events

Definition of a ledger independent of a choice of block

class (Show l, Eq l, NoThunks l, NoThunks (LedgerCfg l), Show (LedgerErr l), Eq (LedgerErr l), NoThunks (LedgerErr l), GetTip l, GetTip (Ticked l)) ⇒ IsLedger l where Source #

Associated Types

type LedgerErr l ∷ Type Source #

Errors that can arise when updating the ledger

This is defined here rather than in ApplyBlock, since the type of these errors does not depend on the type of the block.

type AuxLedgerEvent l ∷ Type Source #

Event emitted by the ledger

TODO we call this AuxLedgerEvent to differentiate from LedgerEvent in InspectLedger. When that module is rewritten to make use of ledger derived events, we may rename this type.

Methods

applyChainTickLedgerResultComputeLedgerEventsLedgerCfg l → SlotNo → l → LedgerResult l (Ticked l) Source #

Apply "slot based" state transformations

When a block is applied to the ledger state, a number of things happen purely based on the slot number of that block. For example:

  • In Byron, scheduled updates are applied, and the update system state is updated.
  • In Shelley, delegation state is updated (on epoch boundaries).

The consensus layer must be able to apply such a "chain tick" function, primarily when validating transactions in the mempool (which, conceptually, live in "some block in the future") or when extracting valid transactions from the mempool to insert into a new block to be produced.

This is not allowed to throw any errors. After all, if this could fail, it would mean a previous block set up the ledger state in such a way that as soon as a certain slot was reached, any block would be invalid.

PRECONDITION: The slot number must be strictly greater than the slot at the tip of the ledger (except for EBBs, obviously..).

NOTE: applyChainTickLedgerResult should not change the tip of the underlying ledger state, which should still refer to the most recent applied block. In other words, we should have

   ledgerTipPoint (applyChainTick cfg slot st)
== ledgerTipPoint st

type family LedgerCfg l ∷ Type Source #

Static environment required for the ledger

Types that inhabit this family will come from the Ledger code.

Link block to its ledger

data ComputeLedgerEvents Source #

Whether we tell the ledger layer to compute ledger events

At the moment events are not emitted in any case in the consensus layer (i.e. there is no handler for those events, nor are they traced), so they are not really forced, we always discard them. This behavior does not incur big costs thanks to laziness.

By passing OmitLedgerEvents we tell the Ledger layer to not even allocate thunks for those events, as we explicitly don't want them.

Instances

Instances details
Generic ComputeLedgerEvents Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Associated Types

type Rep ComputeLedgerEventsTypeType #

Show ComputeLedgerEvents Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Eq ComputeLedgerEvents Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

NoThunks ComputeLedgerEvents Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type Rep ComputeLedgerEvents Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type Rep ComputeLedgerEvents = D1 ('MetaData "ComputeLedgerEvents" "Ouroboros.Consensus.Ledger.Basics" "ouroboros-consensus-0.24.0.0-inplace" 'False) (C1 ('MetaCons "ComputeLedgerEvents" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "OmitLedgerEvents" 'PrefixI 'False) (U1TypeType))

data family LedgerState blk ∷ Type Source #

Ledger state associated with a block

This is the Consensus notion of a ledger state. Each block type is associated with one of the Ledger types for the ledger state. Virtually every concept in this codebase revolves around this type, or the referenced blk. Whenever we use the type variable l, we intend to denote that the expected instantiation is either a LedgerState or some wrapper over it (like the ExtLedgerState).

The main operations we can do with a LedgerState are ticking (defined in IsLedger), and applying a block (defined in ApplyBlock).

Instances

Instances details
Inject LedgerState Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ InjectionIndex xs x → LedgerState x → LedgerState (HardForkBlock xs) Source #

Isomorphic LedgerState Source # 
Instance details

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

Generic (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (Ticked (LedgerState (HardForkBlock xs))) ∷ TypeType #

CanHardFork xs ⇒ Show (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Bridge m a ⇒ Show (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ Eq (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Bridge m a ⇒ Eq (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → Bool #

(/=)LedgerState (DualBlock m a) → LedgerState (DualBlock m a) → Bool #

CanHardFork xs ⇒ NoThunks (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

NoThunks (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ GetTip (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ IsLedger (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ IsLedger (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ ApplyBlock (LedgerState (HardForkBlock xs)) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs)) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (LedgerState (HardForkBlock xs)) Source # 
Instance details

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

Bridge m a ⇒ ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Isomorphic (Ticked :.: LedgerState) Source # 
Instance details

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

type HeaderHash (LedgerState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ Type) = HeaderHash blk
type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.24.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype LedgerState (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data Ticked (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data LedgerState (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Proxy (t ∷ k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
ApplicativeB (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.ApplicativeB

Methods

bpure ∷ (∀ (a ∷ k0). f a) → Proxy f Source #

bprod ∷ ∀ (f ∷ k0 → Type) (g ∷ k0 → Type). Proxy f → Proxy g → Proxy (Product f g) Source #

ConstraintsB (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy Source #

Methods

baddDicts ∷ ∀ (c ∷ k0 → Constraint) (f ∷ k0 → Type). AllB c ProxyProxy f → Proxy (Product (Dict c) f) Source #

DistributiveB (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.DistributiveB

Methods

bdistribute ∷ ∀ f (g ∷ k0 → Type). Functor f ⇒ f (Proxy g) → Proxy (Compose f g) Source #

FunctorB (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.FunctorB

Methods

bmap ∷ (∀ (a ∷ k0). f a → g a) → Proxy f → Proxy g Source #

TraversableB (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.TraversableB

Methods

btraverseApplicative e ⇒ (∀ (a ∷ k0). f a → e (g a)) → Proxy f → e (Proxy g) Source #

Generic1 (Proxy ∷ k → Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy ∷ k → Type #

Methods

from1 ∷ ∀ (a ∷ k0). Proxy a → Rep1 Proxy a #

to1 ∷ ∀ (a ∷ k0). Rep1 Proxy a → Proxy a #

RepeatWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

irepeat ∷ (Void → a) → Proxy a Source #

SemialignWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

ialignWith ∷ (VoidThese a b → c) → Proxy a → Proxy b → Proxy c Source #

ZipWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

izipWith ∷ (Void → a → b → c) → Proxy a → Proxy b → Proxy c Source #

Representable (ProxyTypeType) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy Source #

Methods

tabulate ∷ (Rep Proxy → a) → Proxy a Source #

indexProxy a → Rep Proxy → a Source #

Foldable (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

foldMonoid m ⇒ Proxy m → m #

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

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

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

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

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

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

foldr1 ∷ (a → a → a) → Proxy a → a #

foldl1 ∷ (a → a → a) → Proxy a → a #

toListProxy a → [a] #

nullProxy a → Bool #

lengthProxy a → Int #

elemEq a ⇒ a → Proxy a → Bool #

maximumOrd a ⇒ Proxy a → a #

minimumOrd a ⇒ Proxy a → a #

sumNum a ⇒ Proxy a → a #

productNum a ⇒ Proxy a → a #

Eq1 (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq ∷ (a → b → Bool) → Proxy a → Proxy b → Bool #

Ord1 (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare ∷ (a → b → Ordering) → Proxy a → Proxy b → Ordering #

Read1 (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec ∷ (IntReadS a) → ReadS [a] → IntReadS (Proxy a) #

liftReadList ∷ (IntReadS a) → ReadS [a] → ReadS [Proxy a] #

liftReadPrecReadPrec a → ReadPrec [a] → ReadPrec (Proxy a) #

liftReadListPrecReadPrec a → ReadPrec [a] → ReadPrec [Proxy a] #

Show1 (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec ∷ (Int → a → ShowS) → ([a] → ShowS) → IntProxy a → ShowS #

liftShowList ∷ (Int → a → ShowS) → ([a] → ShowS) → [Proxy a] → ShowS #

Contravariant (ProxyTypeType) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap ∷ (a' → a) → Proxy a → Proxy a' #

(>$) ∷ b → Proxy b → Proxy a #

Traversable (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Alternative (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

emptyProxy a #

(<|>)Proxy a → Proxy a → Proxy a #

someProxy a → Proxy [a] #

manyProxy a → Proxy [a] #

Applicative (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure ∷ a → Proxy a #

(<*>)Proxy (a → b) → Proxy a → Proxy b #

liftA2 ∷ (a → b → c) → Proxy a → Proxy b → Proxy c #

(*>)Proxy a → Proxy b → Proxy b #

(<*)Proxy a → Proxy b → Proxy a #

Functor (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Monad (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=)Proxy a → (a → Proxy b) → Proxy b #

(>>)Proxy a → Proxy b → Proxy b #

return ∷ a → Proxy a #

MonadPlus (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzeroProxy a #

mplusProxy a → Proxy a → Proxy a #

NFData1 (ProxyTypeType)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf ∷ (a → ()) → Proxy a → () #

Hashable1 (ProxyTypeType) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt ∷ (Int → a → Int) → IntProxy a → Int Source #

Align (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

nilProxy a Source #

Repeat (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat ∷ a → Proxy a Source #

Semialign (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

alignProxy a → Proxy b → Proxy (These a b) Source #

alignWith ∷ (These a b → c) → Proxy a → Proxy b → Proxy c Source #

Unalign (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

unalignProxy (These a b) → (Proxy a, Proxy b) Source #

unalignWith ∷ (c → These a b) → Proxy c → (Proxy a, Proxy b) Source #

Unzip (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

unzipWith ∷ (c → (a, b)) → Proxy c → (Proxy a, Proxy b) Source #

unzipProxy (a, b) → (Proxy a, Proxy b) Source #

Zip (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

zipProxy a → Proxy b → Proxy (a, b) Source #

zipWith ∷ (a → b → c) → Proxy a → Proxy b → Proxy c Source #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

memptyProxy s #

mappendProxy s → Proxy s → Proxy s #

mconcat ∷ [Proxy s] → Proxy s #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>)Proxy s → Proxy s → Proxy s #

sconcatNonEmpty (Proxy s) → Proxy s #

stimesIntegral b ⇒ b → Proxy s → Proxy s #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBoundProxy t #

maxBoundProxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succProxy s → Proxy s #

predProxy s → Proxy s #

toEnumIntProxy s #

fromEnumProxy s → Int #

enumFromProxy s → [Proxy s] #

enumFromThenProxy s → Proxy s → [Proxy s] #

enumFromToProxy s → Proxy s → [Proxy s] #

enumFromThenToProxy s → Proxy s → Proxy s → [Proxy s] #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) ∷ TypeType #

Methods

fromProxy t → Rep (Proxy t) x #

toRep (Proxy t) x → Proxy t #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range ∷ (Proxy s, Proxy s) → [Proxy s] #

index ∷ (Proxy s, Proxy s) → Proxy s → Int #

unsafeIndex ∷ (Proxy s, Proxy s) → Proxy s → Int #

inRange ∷ (Proxy s, Proxy s) → Proxy s → Bool #

rangeSize ∷ (Proxy s, Proxy s) → Int #

unsafeRangeSize ∷ (Proxy s, Proxy s) → Int #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrecIntProxy s → ShowS #

showProxy s → String #

showList ∷ [Proxy s] → ShowS #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfProxy a → () #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==)Proxy s → Proxy s → Bool #

(/=)Proxy s → Proxy s → Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compareProxy s → Proxy s → Ordering #

(<)Proxy s → Proxy s → Bool #

(<=)Proxy s → Proxy s → Bool #

(>)Proxy s → Proxy s → Bool #

(>=)Proxy s → Proxy s → Bool #

maxProxy s → Proxy s → Proxy s #

minProxy s → Proxy s → Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntProxy a → Int Source #

hashProxy a → Int Source #

MonoFoldable (Proxy a)

Since: mono-traversable-1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMapMonoid m ⇒ (Element (Proxy a) → m) → Proxy a → m Source #

ofoldr ∷ (Element (Proxy a) → b → b) → b → Proxy a → b Source #

ofoldl' ∷ (a0 → Element (Proxy a) → a0) → a0 → Proxy a → a0 Source #

otoListProxy a → [Element (Proxy a)] Source #

oall ∷ (Element (Proxy a) → Bool) → Proxy a → Bool Source #

oany ∷ (Element (Proxy a) → Bool) → Proxy a → Bool Source #

onullProxy a → Bool Source #

olengthProxy a → Int Source #

olength64Proxy a → Int64 Source #

ocompareLengthIntegral i ⇒ Proxy a → i → Ordering Source #

otraverse_Applicative f ⇒ (Element (Proxy a) → f b) → Proxy a → f () Source #

ofor_Applicative f ⇒ Proxy a → (Element (Proxy a) → f b) → f () Source #

omapM_Applicative m ⇒ (Element (Proxy a) → m ()) → Proxy a → m () Source #

oforM_Applicative m ⇒ Proxy a → (Element (Proxy a) → m ()) → m () Source #

ofoldlMMonad m ⇒ (a0 → Element (Proxy a) → m a0) → a0 → Proxy a → m a0 Source #

ofoldMap1ExSemigroup m ⇒ (Element (Proxy a) → m) → Proxy a → m Source #

ofoldr1Ex ∷ (Element (Proxy a) → Element (Proxy a) → Element (Proxy a)) → Proxy a → Element (Proxy a) Source #

ofoldl1Ex' ∷ (Element (Proxy a) → Element (Proxy a) → Element (Proxy a)) → Proxy a → Element (Proxy a) Source #

headExProxy a → Element (Proxy a) Source #

lastExProxy a → Element (Proxy a) Source #

unsafeHeadProxy a → Element (Proxy a) Source #

unsafeLastProxy a → Element (Proxy a) Source #

maximumByEx ∷ (Element (Proxy a) → Element (Proxy a) → Ordering) → Proxy a → Element (Proxy a) Source #

minimumByEx ∷ (Element (Proxy a) → Element (Proxy a) → Ordering) → Proxy a → Element (Proxy a) Source #

oelemElement (Proxy a) → Proxy a → Bool Source #

onotElemElement (Proxy a) → Proxy a → Bool Source #

MonoFunctor (Proxy a)

Since: mono-traversable-1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap ∷ (Element (Proxy a) → Element (Proxy a)) → Proxy a → Proxy a Source #

MonoPointed (Proxy a)

Since: mono-traversable-1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opointElement (Proxy a) → Proxy a Source #

MonoTraversable (Proxy a)

Since: mono-traversable-1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverseApplicative f ⇒ (Element (Proxy a) → f (Element (Proxy a))) → Proxy a → f (Proxy a) Source #

omapMApplicative m ⇒ (Element (Proxy a) → m (Element (Proxy a))) → Proxy a → m (Proxy a) Source #

Serialise (Proxy a)

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

type AllB (c ∷ k → Constraint) (Proxy ∷ (k → Type) → Type) 
Instance details

Defined in Barbies.Internal.ConstraintsB

type AllB (c ∷ k → Constraint) (Proxy ∷ (k → Type) → Type) = ()
type Rep1 (Proxy ∷ k → Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy ∷ k → Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 ∷ k → Type))
type Rep (ProxyTypeType) 
Instance details

Defined in Data.Functor.Rep

type Rep (ProxyTypeType) = Void
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1TypeType))
type Element (Proxy a) 
Instance details

Defined in Data.MonoTraversable

type Element (Proxy a) = a