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

Ouroboros.Consensus.Util.DepPair

Synopsis

Dependent pairs

type DepPair = GenDepPair I Source #

Dependent pair

A dependent pair is a pair of values where the type of the value depends on the first value.

data GenDepPair g f where Source #

Generalization of DepPair

This adds an additional functor g around the second value in the pair.

Constructors

GenDepPair ∷ !(f a) → !(g a) → GenDepPair g f 

Bundled Patterns

pattern DepPair ∷ f a → a → DepPair f 

Instances

Instances details
(DecodeDiskDepIx f blk, DecodeDiskDep f blk) ⇒ DecodeDisk blk (DepPair (f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDiskCodecConfig blk → ∀ s. Decoder s (DepPair (f blk)) Source #

(EncodeDiskDepIx f blk, EncodeDiskDep f blk) ⇒ EncodeDisk blk (DepPair (f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

encodeDiskCodecConfig blk → DepPair (f blk) → Encoding Source #

DecodeDiskDepIx f blk ⇒ DecodeDisk blk (GenDepPair Serialised (f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDiskCodecConfig blk → ∀ s. Decoder s (GenDepPair Serialised (f blk)) Source #

EncodeDiskDepIx f blk ⇒ EncodeDisk blk (GenDepPair Serialised (f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

encodeDiskCodecConfig blk → GenDepPair Serialised (f blk) → Encoding Source #

(HasNestedContent f blk, ∀ a. Show (g a)) ⇒ Show (GenDepPair g (NestedCtxt f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntGenDepPair g (NestedCtxt f blk) → ShowS Source #

showGenDepPair g (NestedCtxt f blk) → String Source #

showList ∷ [GenDepPair g (NestedCtxt f blk)] → ShowS Source #

depPairFirst ∷ (∀ a. f a → f' a) → GenDepPair g f → GenDepPair g f' Source #

Compare indices

class SameDepIndex f where Source #

Minimal complete definition

Nothing

Methods

sameDepIndex ∷ f a → f b → Maybe (a :~: b) Source #

default sameDepIndexTrivialDependency f ⇒ f a → f b → Maybe (a :~: b) Source #

Instances

Instances details
SameDepIndex QueryAnytime Source # 
Instance details

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

Methods

sameDepIndexQueryAnytime a → QueryAnytime b → Maybe (a :~: b) Source #

SameDepIndex (BlockQuery (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexBlockQuery (DualBlock m a) a0 → BlockQuery (DualBlock m a) b → Maybe (a0 :~: b) Source #

All SingleEraBlock xs ⇒ SameDepIndex (BlockQuery (HardForkBlock xs)) Source # 
Instance details

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

SameDepIndex (BlockQuery blk) ⇒ SameDepIndex (Query blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

sameDepIndexQuery blk a → Query blk b → Maybe (a :~: b) Source #

SameDepIndex (QueryHardFork xs) Source # 
Instance details

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

Methods

sameDepIndexQueryHardFork xs a → QueryHardFork xs b → Maybe (a :~: b) Source #

All SingleEraBlock xs ⇒ SameDepIndex (QueryIfCurrent xs) Source # 
Instance details

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

Methods

sameDepIndexQueryIfCurrent xs a → QueryIfCurrent xs b → Maybe (a :~: b) Source #

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

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

sameDepIndexNestedCtxt f blk a → NestedCtxt f blk b → Maybe (a :~: b) Source #

SameDepIndex (NestedCtxt_ m f) ⇒ SameDepIndex (NestedCtxt_ (DualBlock m a) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexNestedCtxt_ (DualBlock m a) f a0 → NestedCtxt_ (DualBlock m a) f b → Maybe (a0 :~: b) Source #

CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Trivial dependency

class TrivialDependency f where Source #

A dependency is trivial if it always maps to the same type b

Associated Types

type TrivialIndex f ∷ Type Source #

Methods

hasSingleIndex ∷ f a → f b → a :~: b Source #

indexIsTrivial ∷ f (TrivialIndex f) Source #

Instances

Instances details
TrivialDependency (NestedCtxt_ blk f) ⇒ TrivialDependency (NestedCtxt f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Associated Types

type TrivialIndex (NestedCtxt f blk) Source #

Methods

hasSingleIndexNestedCtxt f blk a → NestedCtxt f blk b → a :~: b Source #

indexIsTrivialNestedCtxt f blk (TrivialIndex (NestedCtxt f blk)) Source #

Convenience re-exports

data Proxy (t ∷ k) Source #

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
Generic1 (Proxy ∷ k → Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy ∷ k → Type Source #

Methods

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

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

SemialignWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

ialignWith ∷ (Void → These a b → c) → Proxy a → Proxy b → Proxy c

ZipWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

Defined in Barbies.Internal.ConstraintsB

Associated Types

type AllB c Proxy

Methods

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

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

Defined in Barbies.Internal.FunctorB

Methods

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

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

Defined in Barbies.Internal.ApplicativeB

Methods

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

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

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)

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)

RepeatWithIndex Void (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

irepeat ∷ (Void → a) → Proxy a

Monad (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

return ∷ a → Proxy a Source #

Functor (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Applicative (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure ∷ a → Proxy a Source #

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

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

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

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

Foldable (ProxyTypeType)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

foldMonoid m ⇒ Proxy m → m Source #

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

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

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

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

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

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

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

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

toListProxy a → [a] Source #

nullProxy a → Bool Source #

lengthProxy a → Int Source #

elemEq a ⇒ a → Proxy a → Bool Source #

maximumOrd a ⇒ Proxy a → a Source #

minimumOrd a ⇒ Proxy a → a Source #

sumNum a ⇒ Proxy a → a Source #

productNum a ⇒ Proxy a → a Source #

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) Source #

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

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

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

Contravariant (ProxyTypeType) 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap ∷ (a → b) → Proxy b → Proxy a Source #

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

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 Source #

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 Source #

Read1 (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

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

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 Source #

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

Alternative (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

emptyProxy a Source #

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

someProxy a → Proxy [a] Source #

manyProxy a → Proxy [a] Source #

MonadPlus (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzeroProxy a Source #

mplusProxy a → Proxy a → Proxy a Source #

NFData1 (ProxyTypeType)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Hashable1 (ProxyTypeType) 
Instance details

Defined in Data.Hashable.Class

Methods

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

Align (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

nilProxy a

Semialign (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

Zip (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

Representable (ProxyTypeType) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy

Methods

tabulate ∷ (Rep Proxy → a) → Proxy a

indexProxy a → Rep Proxy → a

Unalign (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

Repeat (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

repeat ∷ a → Proxy a

Unzip (ProxyTypeType) 
Instance details

Defined in Data.Semialign.Internal

Methods

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

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

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succProxy s → Proxy s Source #

predProxy s → Proxy s Source #

toEnumIntProxy s Source #

fromEnumProxy s → Int Source #

enumFromProxy s → [Proxy s] Source #

enumFromThenProxy s → Proxy s → [Proxy s] Source #

enumFromToProxy s → Proxy s → [Proxy s] Source #

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

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compareProxy s → Proxy s → Ordering Source #

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

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

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

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

maxProxy s → Proxy s → Proxy s Source #

minProxy s → Proxy s → Proxy s Source #

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 Source #

showProxy s → String Source #

showList ∷ [Proxy s] → ShowS Source #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

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

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

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

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

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) ∷ TypeType Source #

Methods

fromProxy t → Rep (Proxy t) x Source #

toRep (Proxy t) x → Proxy t Source #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

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

sconcatNonEmpty (Proxy s) → Proxy s Source #

stimesIntegral b ⇒ b → Proxy s → Proxy s Source #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

memptyProxy s Source #

mappendProxy s → Proxy s → Proxy s Source #

mconcat ∷ [Proxy s] → Proxy s Source #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfProxy a → () Source #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntProxy a → Int

hashProxy a → Int

Serialise (Proxy a) 
Instance details

Defined in Codec.Serialise.Class

Methods

encodeProxy a → Encoding

decode ∷ Decoder s (Proxy a)

encodeList ∷ [Proxy a] → Encoding

decodeList ∷ Decoder s [Proxy a]

MonoFoldable (Proxy a) 
Instance details

Defined in Data.MonoTraversable

Methods

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

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

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

otoListProxy a → [Element (Proxy a)]

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

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

onullProxy a → Bool

olengthProxy a → Int

olength64Proxy a → Int64

ocompareLengthIntegral i ⇒ Proxy a → i → Ordering

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

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

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

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

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

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

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

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

headExProxy a → Element (Proxy a)

lastExProxy a → Element (Proxy a)

unsafeHeadProxy a → Element (Proxy a)

unsafeLastProxy a → Element (Proxy a)

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

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

oelem ∷ Element (Proxy a) → Proxy a → Bool

onotElem ∷ Element (Proxy a) → Proxy a → Bool

MonoTraversable (Proxy a) 
Instance details

Defined in Data.MonoTraversable

Methods

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

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

MonoFunctor (Proxy a) 
Instance details

Defined in Data.MonoTraversable

Methods

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

MonoPointed (Proxy a) 
Instance details

Defined in Data.MonoTraversable

Methods

opoint ∷ Element (Proxy a) → Proxy a

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) 
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) 
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

data (a ∷ k) :~: (b ∷ k) where infix 4 Source #

Propositional equality. If a :~: b is inhabited by some terminating value, then the type a is the same as the type b. To use this equality in practice, pattern-match on the a :~: b to get out the Refl constructor; in the body of the pattern-match, the compiler knows that a ~ b.

Since: base-4.7.0.0

Constructors

Refl ∷ ∀ k (a ∷ k). a :~: a 

Instances

Instances details
TestEquality ((:~:) a ∷ k → Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

testEquality ∷ ∀ (a0 ∷ k0) (b ∷ k0). (a :~: a0) → (a :~: b) → Maybe (a0 :~: b) Source #

GEq ((:~:) a ∷ k → Type) 
Instance details

Defined in Data.GADT.Internal

Methods

geq ∷ ∀ (a0 ∷ k0) (b ∷ k0). (a :~: a0) → (a :~: b) → Maybe (a0 :~: b)

GShow ((:~:) a ∷ k → Type) 
Instance details

Defined in Data.GADT.Internal

Methods

gshowsPrec ∷ ∀ (a0 ∷ k0). Int → (a :~: a0) → ShowS

GCompare ((:~:) a ∷ k → Type) 
Instance details

Defined in Data.GADT.Internal

Methods

gcompare ∷ ∀ (a0 ∷ k0) (b ∷ k0). (a :~: a0) → (a :~: b) → GOrdering a0 b

GRead ((:~:) a ∷ k → Type) 
Instance details

Defined in Data.GADT.Internal

Methods

greadsPrecInt → GReadS ((:~:) a)

NFData2 ((:~:)TypeTypeType)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 ∷ (a → ()) → (b → ()) → (a :~: b) → () Source #

NFData1 ((:~:) a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf ∷ (a0 → ()) → (a :~: a0) → () Source #

a ~ b ⇒ Bounded (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

minBound ∷ a :~: b Source #

maxBound ∷ a :~: b Source #

a ~ b ⇒ Enum (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

succ ∷ (a :~: b) → a :~: b Source #

pred ∷ (a :~: b) → a :~: b Source #

toEnumInt → a :~: b Source #

fromEnum ∷ (a :~: b) → Int Source #

enumFrom ∷ (a :~: b) → [a :~: b] Source #

enumFromThen ∷ (a :~: b) → (a :~: b) → [a :~: b] Source #

enumFromTo ∷ (a :~: b) → (a :~: b) → [a :~: b] Source #

enumFromThenTo ∷ (a :~: b) → (a :~: b) → (a :~: b) → [a :~: b] Source #

Eq (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

(==) ∷ (a :~: b) → (a :~: b) → Bool Source #

(/=) ∷ (a :~: b) → (a :~: b) → Bool Source #

Ord (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

compare ∷ (a :~: b) → (a :~: b) → Ordering Source #

(<) ∷ (a :~: b) → (a :~: b) → Bool Source #

(<=) ∷ (a :~: b) → (a :~: b) → Bool Source #

(>) ∷ (a :~: b) → (a :~: b) → Bool Source #

(>=) ∷ (a :~: b) → (a :~: b) → Bool Source #

max ∷ (a :~: b) → (a :~: b) → a :~: b Source #

min ∷ (a :~: b) → (a :~: b) → a :~: b Source #

a ~ b ⇒ Read (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrecInt → (a :~: b) → ShowS Source #

show ∷ (a :~: b) → String Source #

showList ∷ [a :~: b] → ShowS Source #

NFData (a :~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a :~: b) → () Source #