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

Data.SOP.Strict

Description

Strict variant of SOP

This does not currently attempt to be exhaustive.

Synopsis

NP

data NP :: (k -> Type ) -> [k] -> Type where Source #

Constructors

Nil :: NP f '[]
(:*) :: !(f x) -> !( NP f xs) -> NP f (x ': xs) infixr 5

Instances

Instances details
HTrans ( NP :: (k1 -> Type ) -> [k1] -> Type ) ( NP :: (k2 -> Type ) -> [k2] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NP ) ( LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source #

HPure ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => ( forall (a :: k0). f a) -> NP f xs Source #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> ( forall (a :: k0). c a => f a) -> NP f xs Source #

HAp ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs Source #

HCollapse ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP ( K a) xs -> CollapseTo NP a Source #

HTraverse_ ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source #

HSequence ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f ( NP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

All ( Compose Eq f) xs => Eq ( NP f xs) Source #
Instance details

Defined in Data.SOP.Strict

( All ( Compose Eq f) xs, All ( Compose Ord f) xs) => Ord ( NP f xs) Source #
Instance details

Defined in Data.SOP.Strict

All ( Compose Show f) xs => Show ( NP f xs) Source #

Copied from sop-core

Not derived, since derived instance ignores associativity info

Instance details

Defined in Data.SOP.Strict

All ( Compose NoThunks f) xs => NoThunks ( NP f xs) Source #
Instance details

Defined in Data.SOP.Strict

type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint ) = AllZip c
type Same ( NP :: (k1 -> Type ) -> [k1] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Same ( NP :: (k1 -> Type ) -> [k1] -> Type ) = NP :: (k2 -> Type ) -> [k2] -> Type
type Prod ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Prod ( NP :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type SListIN ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type SListIN ( NP :: (k -> Type ) -> [k] -> Type ) = SListI :: [k] -> Constraint
type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a Source #
Instance details

Defined in Data.SOP.Strict

type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a = [a]
type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c

hd :: NP f (x ': xs) -> f x Source #

tl :: NP f (x ': xs) -> NP f xs Source #

NS

data NS :: (k -> Type ) -> [k] -> Type where Source #

Constructors

Z :: !(f x) -> NS f (x ': xs)
S :: !( NS f xs) -> NS f (x ': xs)

Instances

Instances details
HTrans ( NS :: (k1 -> Type ) -> [k1] -> Type ) ( NS :: (k2 -> Type ) -> [k2] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NS ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NS ) ( LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source #

HAp ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs Source #

HCollapse ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS ( K a) xs -> CollapseTo NS a Source #

HSequence ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f ( NS g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NS c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NS xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

HExpand ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod NS ) xs => ( forall (x :: k0). f x) -> NS f xs -> Prod NS f xs Source #

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod NS ) c xs => proxy c -> ( forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs Source #

All ( Compose Eq f) xs => Eq ( NS f xs) Source #
Instance details

Defined in Data.SOP.Strict

( All ( Compose Eq f) xs, All ( Compose Ord f) xs) => Ord ( NS f xs) Source #
Instance details

Defined in Data.SOP.Strict

All ( Compose Show f) xs => Show ( NS f xs) Source #
Instance details

Defined in Data.SOP.Strict

All ( Compose NoThunks f) xs => NoThunks ( NS f xs) Source #
Instance details

Defined in Data.SOP.Strict

type Same ( NS :: (k1 -> Type ) -> [k1] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Same ( NS :: (k1 -> Type ) -> [k1] -> Type ) = NS :: (k2 -> Type ) -> [k2] -> Type
type Prod ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Prod ( NS :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type SListIN ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type SListIN ( NS :: (k -> Type ) -> [k] -> Type ) = SListI :: [k] -> Constraint
type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a Source #
Instance details

Defined in Data.SOP.Strict

type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a = a
type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c

index_NS :: forall f xs. NS f xs -> Int Source #

unZ :: NS f '[x] -> f x Source #

Injections

type Injection (f :: k -> Type ) (xs :: [k]) = f -.-> K ( NS f xs) Source #

Re-exports from sop-core

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 :: forall (a :: k0). Proxy a -> Rep1 Proxy a Source #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a Source #

SemialignWithIndex Void ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

ZipWithIndex Void ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Methods

izipWith :: ( Void -> a -> b -> c) -> Proxy a -> Proxy b -> Proxy c Source #

RepeatWithIndex Void ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Monad ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Functor ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Applicative ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Foldable ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Traversable ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

MonadPlus ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Alternative ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Contravariant ( Proxy :: Type -> Type )
Instance details

Defined in Data.Functor.Contravariant

Eq1 ( Proxy :: Type -> Type )

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 ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Read1 ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Show1 ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

NFData1 ( Proxy :: Type -> Type )

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () Source #

Hashable1 ( Proxy :: Type -> Type )
Instance details

Defined in Data.Hashable.Class

Semialign ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Align ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Unalign ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Zip ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Repeat ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

Unzip ( Proxy :: Type -> Type )
Instance details

Defined in Data.Semialign.Internal

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

Eq ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Ord ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

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

Ix ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Generic ( Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( Proxy t) :: Type -> Type Source #

Semigroup ( Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Monoid ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Hashable ( Proxy a)
Instance details

Defined in Data.Hashable.Class

NFData ( Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () Source #

Serialise ( Proxy a)

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

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 ( Proxy t)
Instance details

Defined in GHC.Generics

type Rep ( Proxy t) = D1 (' MetaData "Proxy" "Data.Proxy" "base" ' False ) ( C1 (' MetaCons "Proxy" ' PrefixI ' False ) ( U1 :: Type -> Type ))

ccompare_SOP Source #

Arguments

:: forall k (c :: k -> Constraint ) proxy r (f :: k -> Type ) (g :: k -> Type ) (xss :: [[k]]). All2 c xss
=> proxy c
-> r

what to do if first is smaller

-> ( forall (xs :: [k]). All c xs => NP f xs -> NP g xs -> r)

what to do if both are equal

-> r

what to do if first is larger

-> SOP f xss
-> SOP g xss
-> r

Constrained version of compare_SOP .

Since: sop-core-0.3.2.0

compare_SOP Source #

Arguments

:: forall k r (f :: k -> Type ) (g :: k -> Type ) (xss :: [[k]]). r

what to do if first is smaller

-> ( forall (xs :: [k]). NP f xs -> NP g xs -> r)

what to do if both are equal

-> r

what to do if first is larger

-> SOP f xss
-> SOP g xss
-> r

Compare two sums of products with respect to the choice in the sum they are making.

Only the sum structure is used for comparison. This is a small wrapper around ccompare_NS for a common special case.

Since: sop-core-0.3.2.0

ccompare_NS Source #

Arguments

:: forall k c proxy r f g (xs :: [k]). All c xs
=> proxy c
-> r

what to do if first is smaller

-> ( forall (x :: k). c x => f x -> g x -> r)

what to do if both are equal

-> r

what to do if first is larger

-> NS f xs
-> NS g xs
-> r

Constrained version of compare_NS .

Since: sop-core-0.3.2.0

compare_NS Source #

Arguments

:: forall k r f g (xs :: [k]). r

what to do if first is smaller

-> ( forall (x :: k). f x -> g x -> r)

what to do if both are equal

-> r

what to do if first is larger

-> NS f xs
-> NS g xs
-> r

Compare two sums with respect to the choice they are making.

A value that chooses the first option is considered smaller than one that chooses the second option.

If the choices are different, then either the first (if the first is smaller than the second) or the third (if the first is larger than the second) argument are called. If both choices are equal, then the second argument is called, which has access to the elements contained in the sums.

Since: sop-core-0.3.2.0

apInjs_POP :: forall k (xss :: [[k]]) (f :: k -> Type ). SListI xss => POP f xss -> [ SOP f xss] Source #

Apply injections to a product of product.

This operates on the outer product only. Given a product containing all possible choices (that are products), produce a list of sums (of products) by applying each injection to the appropriate element.

Example:

>>> apInjs_POP (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil))
[SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]

apInjs_NP :: forall k (xs :: [k]) (f :: k -> Type ). SListI xs => NP f xs -> [ NS f xs] Source #

Apply injections to a product.

Given a product containing all possible choices, produce a list of sums by applying each injection to the appropriate element.

Example:

>>> apInjs_NP (I 'x' :* I True :* I 2 :* Nil)
[Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]

shift :: forall a1 (f :: a1 -> Type ) (xs :: [a1]) (a2 :: a1) (x :: a1). Injection f xs a2 -> Injection f (x ': xs) a2 Source #

Shift an injection.

Given an injection, return an injection into a sum that is one component larger.

unSOP :: forall k (f :: k -> Type ) (xss :: [[k]]). SOP f xss -> NS ( NP f) xss Source #

Unwrap a sum of products.

newtype SOP (f :: k -> Type ) (xss :: [[k]]) Source #

A sum of products.

This is a 'newtype' for an NS of an NP . The elements of the (inner) products are applications of the parameter f . The type SOP is indexed by the list of lists that determines the sizes of both the (outer) sum and all the (inner) products, as well as the types of all the elements of the inner products.

A SOP I reflects the structure of a normal Haskell datatype. The sum structure represents the choice between the different constructors, the product structure represents the arguments of each constructor.

Constructors

SOP ( NS ( NP f) xss)

Instances

Instances details
HTrans ( SOP :: (k1 -> Type ) -> [[k1]] -> Type ) ( SOP :: (k2 -> Type ) -> [[k2]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod SOP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod SOP ) ( LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys Source #

HAp ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs Source #

HCollapse ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN SOP xs => SOP ( K a) xs -> CollapseTo SOP a Source #

HTraverse_ ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN SOP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN SOP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> SOP f xs -> g () Source #

HSequence ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f ( SOP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN SOP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g ( SOP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN SOP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g ( SOP f' xs) Source #

HIndex ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type ) (xs :: l). SOP f xs -> Int Source #

HApInjs ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type ). SListIN SOP xs => Prod SOP f xs -> [ SOP f xs] Source #

HExpand ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod SOP ) xs => ( forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs Source #

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod SOP ) c xs => proxy c -> ( forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs Source #

Eq ( NS ( NP f) xss) => Eq ( SOP f xss)
Instance details

Defined in Data.SOP.NS

Ord ( NS ( NP f) xss) => Ord ( SOP f xss)
Instance details

Defined in Data.SOP.NS

Show ( NS ( NP f) xss) => Show ( SOP f xss)
Instance details

Defined in Data.SOP.NS

NFData ( NS ( NP f) xss) => NFData ( SOP f xss)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NS

Methods

rnf :: SOP f xss -> () Source #

type Same ( SOP :: (k1 -> Type ) -> [[k1]] -> Type )
Instance details

Defined in Data.SOP.NS

type Same ( SOP :: (k1 -> Type ) -> [[k1]] -> Type ) = SOP :: (k2 -> Type ) -> [[k2]] -> Type
type Prod ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

type Prod ( SOP :: (k -> Type ) -> [[k]] -> Type ) = POP :: (k -> Type ) -> [[k]] -> Type
type SListIN ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

type SListIN ( SOP :: (k -> Type ) -> [[k]] -> Type ) = SListI2 :: [[k]] -> Constraint
type CollapseTo ( SOP :: (k -> Type ) -> [[k]] -> Type ) a
Instance details

Defined in Data.SOP.NS

type CollapseTo ( SOP :: (k -> Type ) -> [[k]] -> Type ) a = [a]
type AllN ( SOP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NS

type AllN ( SOP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint ) = All2 c

hcliftA3' :: forall k (c :: k -> Constraint ) (xss :: [[k]]) h proxy f f' f'' f'''. ( All2 c xss, Prod h ~ ( NP :: ([k] -> Type ) -> [[k]] -> Type ), HAp h) => proxy c -> ( forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss Source #

Like hcliftA' , but for ternary functions.

hcliftA2' :: forall k (c :: k -> Constraint ) (xss :: [[k]]) h proxy f f' f''. ( All2 c xss, Prod h ~ ( NP :: ([k] -> Type ) -> [[k]] -> Type ), HAp h) => proxy c -> ( forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss Source #

Like hcliftA' , but for binary functions.

hcliftA' :: forall k (c :: k -> Constraint ) (xss :: [[k]]) h proxy f f'. ( All2 c xss, Prod h ~ ( NP :: ([k] -> Type ) -> [[k]] -> Type ), HAp h) => proxy c -> ( forall (xs :: [k]). All c xs => f xs -> f' xs) -> h f xss -> h f' xss Source #

Lift a constrained function operating on a list-indexed structure to a function on a list-of-list-indexed structure.

This is a variant of hcliftA .

Specification:

hcliftA' p f xs = hpure (fn_2 $ \ AllDictC -> f) ` hap ` allDict_NP p ` hap ` xs

Instances:

hcliftA' :: All2 c xss => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> NP f xss -> NP f' xss
hcliftA' :: All2 c xss => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> NS f xss -> NS f' xss

shiftProjection :: forall a1 (f :: a1 -> Type ) (xs :: [a1]) (a2 :: a1) (x :: a1). Projection f xs a2 -> Projection f (x ': xs) a2 Source #

projections :: forall k (xs :: [k]) (f :: k -> Type ). SListI xs => NP ( Projection f xs) xs Source #

Compute all projections from an n-ary product.

Each element of the resulting product contains one of the projections.

fromList :: forall k (xs :: [k]) a. SListI xs => [a] -> Maybe ( NP ( K a :: k -> Type ) xs) Source #

Construct a homogeneous n-ary product from a normal Haskell list.

Returns Nothing if the length of the list does not exactly match the expected size of the product.

unPOP :: forall k (f :: k -> Type ) (xss :: [[k]]). POP f xss -> NP ( NP f) xss Source #

Unwrap a product of products.

newtype POP (f :: k -> Type ) (xss :: [[k]]) Source #

A product of products.

This is a 'newtype' for an NP of an NP . The elements of the inner products are applications of the parameter f . The type POP is indexed by the list of lists that determines the lengths of both the outer and all the inner products, as well as the types of all the elements of the inner products.

A POP is reminiscent of a two-dimensional table (but the inner lists can all be of different length). In the context of the SOP approach to generic programming, a POP is useful to represent information that is available for all arguments of all constructors of a datatype.

Constructors

POP ( NP ( NP f) xss)

Instances

Instances details
HTrans ( POP :: (k1 -> Type ) -> [[k1]] -> Type ) ( POP :: (k2 -> Type ) -> [[k2]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod POP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod POP ) ( LiftedCoercible f g) xs ys => POP f xs -> POP g ys Source #

HPure ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN POP xs => ( forall (a :: k0). f a) -> POP f xs Source #

hcpure :: forall c (xs :: l) proxy f. AllN POP c xs => proxy c -> ( forall (a :: k0). c a => f a) -> POP f xs Source #

HAp ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod POP (f -.-> g) xs -> POP f xs -> POP g xs Source #

HCollapse ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN POP xs => POP ( K a) xs -> CollapseTo POP a Source #

HTraverse_ ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN POP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN POP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> POP f xs -> g () Source #

HSequence ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f ( POP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN POP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g ( POP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN POP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g ( POP f' xs) Source #

Eq ( NP ( NP f) xss) => Eq ( POP f xss)
Instance details

Defined in Data.SOP.NP

Ord ( NP ( NP f) xss) => Ord ( POP f xss)
Instance details

Defined in Data.SOP.NP

Show ( NP ( NP f) xss) => Show ( POP f xss)
Instance details

Defined in Data.SOP.NP

Semigroup ( NP ( NP f) xss) => Semigroup ( POP f xss)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

Monoid ( NP ( NP f) xss) => Monoid ( POP f xss)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.NP

NFData ( NP ( NP f) xss) => NFData ( POP f xss)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.NP

Methods

rnf :: POP f xss -> () Source #

type AllZipN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: a -> b -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllZipN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: a -> b -> Constraint ) = AllZip2 c
type Same ( POP :: (k1 -> Type ) -> [[k1]] -> Type )
Instance details

Defined in Data.SOP.NP

type Same ( POP :: (k1 -> Type ) -> [[k1]] -> Type ) = POP :: (k2 -> Type ) -> [[k2]] -> Type
type Prod ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

type Prod ( POP :: (k -> Type ) -> [[k]] -> Type ) = POP :: (k -> Type ) -> [[k]] -> Type
type UnProd ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

type UnProd ( POP :: (k -> Type ) -> [[k]] -> Type ) = SOP :: (k -> Type ) -> [[k]] -> Type
type SListIN ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

type SListIN ( POP :: (k -> Type ) -> [[k]] -> Type ) = SListI2 :: [[k]] -> Constraint
type CollapseTo ( POP :: (k -> Type ) -> [[k]] -> Type ) a
Instance details

Defined in Data.SOP.NP

type CollapseTo ( POP :: (k -> Type ) -> [[k]] -> Type ) a = [[a]]
type AllN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint ) = All2 c

type Projection (f :: k -> Type ) (xs :: [k]) = ( K ( NP f xs) :: k -> Type ) -.-> f Source #

The type of projections from an n-ary product.

A projection is a function from the n-ary product to a single element.

lengthSList :: forall k (xs :: [k]) proxy. SListI xs => proxy xs -> Int Source #

The length of a type-level list.

Since: sop-core-0.2

shape :: forall k (xs :: [k]). SListI xs => Shape xs Source #

The shape of a type-level list.

sList :: forall k (xs :: [k]). SListI xs => SList xs Source #

Get hold of an explicit singleton (that one can then pattern match on) for a type-level list

case_SList :: forall k (xs :: [k]) r. SListI xs => r ('[] :: [k]) -> ( forall (y :: k) (ys :: [k]). SListI ys => r (y ': ys)) -> r xs Source #

Case distinction on a type-level list.

Since: sop-core-0.4.0.0

para_SList :: forall k (xs :: [k]) r. SListI xs => r ('[] :: [k]) -> ( forall (y :: k) (ys :: [k]). SListI ys => r ys -> r (y ': ys)) -> r xs Source #

Paramorphism for a type-level list.

Since: sop-core-0.4.0.0

data SList (a :: [k]) where Source #

Explicit singleton list.

A singleton list can be used to reveal the structure of a type-level list argument that the function is quantified over. For every type-level list xs , there is one non-bottom value of type SList xs .

Note that these singleton lists are polymorphic in the list elements; we do not require a singleton representation for them.

Since: sop-core-0.2

Constructors

SNil :: forall k. SList ('[] :: [k])
SCons :: forall k (xs :: [k]) (x :: k). SListI xs => SList (x ': xs)

data Shape (a :: [k]) where Source #

Occasionally it is useful to have an explicit, term-level, representation of type-level lists (esp because of https://ghc.haskell.org/trac/ghc/ticket/9108 )

Constructors

ShapeNil :: forall k. Shape ('[] :: [k])
ShapeCons :: forall k (xs :: [k]) (x :: k). SListI xs => Shape xs -> Shape (x ': xs)

htoI :: forall k1 l1 l2 h1 (f :: k1 -> Type ) (xs :: l1) (ys :: l2) h2. ( AllZipN ( Prod h1) ( LiftedCoercible f I ) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys Source #

Specialization of hcoerce .

Since: sop-core-0.3.1.0

hfromI :: forall l1 k2 l2 h1 (f :: k2 -> Type ) (xs :: l1) (ys :: l2) h2. ( AllZipN ( Prod h1) ( LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys Source #

Specialization of hcoerce .

Since: sop-core-0.3.1.0

hsequenceK :: forall k l h (xs :: l) f a. ( SListIN h xs, SListIN ( Prod h) xs, Applicative f, HSequence h) => h ( K (f a) :: k -> Type ) xs -> f (h ( K a :: k -> Type ) xs) Source #

Special case of hsequence' where g = K a .

hsequence :: forall l h (xs :: l) f. ( SListIN h xs, SListIN ( Prod h) xs, HSequence h, Applicative f) => h f xs -> f (h I xs) Source #

Special case of hsequence' where g = I .

hcfor :: forall l h c (xs :: l) g proxy f. ( HSequence h, AllN h c xs, Applicative g) => proxy c -> h f xs -> ( forall a. c a => f a -> g a) -> g (h I xs) Source #

Flipped version of hctraverse .

Since: sop-core-0.3.2.0

hctraverse :: forall l h c (xs :: l) g proxy f. ( HSequence h, AllN h c xs, Applicative g) => proxy c -> ( forall a. c a => f a -> g a) -> h f xs -> g (h I xs) Source #

Special case of hctraverse' where f' = I .

Since: sop-core-0.3.2.0

hcfoldMap :: forall k l h c (xs :: l) m proxy f. ( HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> ( forall (a :: k). c a => f a -> m) -> h f xs -> m Source #

Special case of hctraverse_ .

Since: sop-core-0.3.2.0

hcfor_ :: forall k l h c (xs :: l) g proxy f. ( HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> ( forall (a :: k). c a => f a -> g ()) -> g () Source #

Flipped version of hctraverse_ .

Since: sop-core-0.3.2.0

hczipWith3 :: forall k l h c (xs :: l) proxy f f' f'' f'''. ( AllN ( Prod h) c xs, HAp h, HAp ( Prod h)) => proxy c -> ( forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #

Another name for hcliftA3 .

Since: sop-core-0.2

hczipWith :: forall k l h c (xs :: l) proxy f f' f''. ( AllN ( Prod h) c xs, HAp h, HAp ( Prod h)) => proxy c -> ( forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #

Another name for hcliftA2 .

Since: sop-core-0.2

hcmap :: forall k l h c (xs :: l) proxy f f'. ( AllN ( Prod h) c xs, HAp h) => proxy c -> ( forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs Source #

Another name for hcliftA .

Since: sop-core-0.2

hcliftA3 :: forall k l h c (xs :: l) proxy f f' f'' f'''. ( AllN ( Prod h) c xs, HAp h, HAp ( Prod h)) => proxy c -> ( forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #

Variant of hliftA3 that takes a constrained function.

Specification:

hcliftA3 p f xs ys zs = hcpure p (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

hcliftA2 :: forall k l h c (xs :: l) proxy f f' f''. ( AllN ( Prod h) c xs, HAp h, HAp ( Prod h)) => proxy c -> ( forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #

Variant of hliftA2 that takes a constrained function.

Specification:

hcliftA2 p f xs ys = hcpure p (fn_2 f) ` hap ` xs ` hap ` ys

hcliftA :: forall k l h c (xs :: l) proxy f f'. ( AllN ( Prod h) c xs, HAp h) => proxy c -> ( forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs Source #

Variant of hliftA that takes a constrained function.

Specification:

hcliftA p f xs = hcpure p (fn f) ` hap ` xs

hzipWith3 :: forall k l h (xs :: l) f f' f'' f'''. ( SListIN ( Prod h) xs, HAp h, HAp ( Prod h)) => ( forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #

Another name for hliftA3 .

Since: sop-core-0.2

hzipWith :: forall k l h (xs :: l) f f' f''. ( SListIN ( Prod h) xs, HAp h, HAp ( Prod h)) => ( forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #

Another name for hliftA2 .

Since: sop-core-0.2

hmap :: forall k l h (xs :: l) f f'. ( SListIN ( Prod h) xs, HAp h) => ( forall (a :: k). f a -> f' a) -> h f xs -> h f' xs Source #

Another name for hliftA .

Since: sop-core-0.2

hliftA3 :: forall k l h (xs :: l) f f' f'' f'''. ( SListIN ( Prod h) xs, HAp h, HAp ( Prod h)) => ( forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs Source #

A generalized form of liftA3 , which in turn is a generalized zipWith3 .

Takes a lifted ternary function and uses it to combine three structures of equal shape into a single structure.

It either takes three product structures to a product structure, or two product structures and one sum structure to a sum structure.

Specification:

hliftA3 f xs ys zs = hpure (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

Instances:

hliftA3, liftA3_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs  -> NP  f''' xs
hliftA3, liftA3_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NS  f'' xs  -> NS  f''' xs
hliftA3, liftA3_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> POP f'' xss -> POP f''' xs
hliftA3, liftA3_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> SOP f'' xss -> SOP f''' xs

hliftA2 :: forall k l h (xs :: l) f f' f''. ( SListIN ( Prod h) xs, HAp h, HAp ( Prod h)) => ( forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source #

A generalized form of liftA2 , which in turn is a generalized zipWith .

Takes a lifted binary function and uses it to combine two structures of equal shape into a single structure.

It either takes two product structures to a product structure, or one product and one sum structure to a sum structure.

Specification:

hliftA2 f xs ys = hpure (fn_2 f) ` hap ` xs ` hap ` ys

Instances:

hliftA2, liftA2_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs
hliftA2, liftA2_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NS  f' xs  -> NS  f'' xs
hliftA2, liftA2_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> POP f' xss -> POP f'' xss
hliftA2, liftA2_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> SOP f' xss -> SOP f'' xss

hliftA :: forall k l h (xs :: l) f f'. ( SListIN ( Prod h) xs, HAp h) => ( forall (a :: k). f a -> f' a) -> h f xs -> h f' xs Source #

A generalized form of liftA , which in turn is a generalized map .

Takes a lifted function and applies it to every element of a structure while preserving its shape.

Specification:

hliftA f xs = hpure (fn f) ` hap ` xs

Instances:

hliftA, liftA_NP  :: SListI  xs  => (forall a. f a -> f' a) -> NP  f xs  -> NP  f' xs
hliftA, liftA_NS  :: SListI  xs  => (forall a. f a -> f' a) -> NS  f xs  -> NS  f' xs
hliftA, liftA_POP :: SListI2 xss => (forall a. f a -> f' a) -> POP f xss -> POP f' xss
hliftA, liftA_SOP :: SListI2 xss => (forall a. f a -> f' a) -> SOP f xss -> SOP f' xss

fn_4 :: forall k f (a :: k) f' f'' f''' f''''. (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a Source #

Construct a quarternary lifted function.

fn_3 :: forall k f (a :: k) f' f'' f'''. (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a Source #

Construct a ternary lifted function.

fn_2 :: forall k f (a :: k) f' f''. (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a Source #

Construct a binary lifted function.

fn :: forall k f (a :: k) f'. (f a -> f' a) -> (f -.-> f') a Source #

Construct a lifted function.

Same as Fn . Only available for uniformity with the higher-arity versions.

class HPure (h :: (k -> Type ) -> l -> Type ) where Source #

A generalization of pure or return to higher kinds.

Methods

hpure :: forall (xs :: l) f. SListIN h xs => ( forall (a :: k). f a) -> h f xs Source #

Corresponds to pure directly.

Instances:

hpure, pure_NP  :: SListI  xs  => (forall a. f a) -> NP  f xs
hpure, pure_POP :: SListI2 xss => (forall a. f a) -> POP f xss

hcpure :: forall c (xs :: l) proxy f. AllN h c xs => proxy c -> ( forall (a :: k). c a => f a) -> h f xs Source #

A variant of hpure that allows passing in a constrained argument.

Calling hcpure f s where s :: h f xs causes f to be applied at all the types that are contained in xs . Therefore, the constraint c has to be satisfied for all elements of xs , which is what AllN h c xs states.

Instances:

hcpure, cpure_NP  :: (All  c xs ) => proxy c -> (forall a. c a => f a) -> NP  f xs
hcpure, cpure_POP :: (All2 c xss) => proxy c -> (forall a. c a => f a) -> POP f xss

Instances

Instances details
HPure ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => ( forall (a :: k0). f a) -> NP f xs Source #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> ( forall (a :: k0). c a => f a) -> NP f xs Source #

HPure ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => ( forall (a :: k0). f a) -> NP f xs Source #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> ( forall (a :: k0). c a => f a) -> NP f xs Source #

HPure ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN POP xs => ( forall (a :: k0). f a) -> POP f xs Source #

hcpure :: forall c (xs :: l) proxy f. AllN POP c xs => proxy c -> ( forall (a :: k0). c a => f a) -> POP f xs Source #

newtype ((f :: k -> Type ) -.-> (g :: k -> Type )) (a :: k) infixr 1 Source #

Lifted functions.

Constructors

Fn

Fields

type family Prod (h :: (k -> Type ) -> l -> Type ) :: (k -> Type ) -> l -> Type Source #

Maps a structure containing sums to the corresponding product structure.

Instances

Instances details
type Prod ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Prod ( NP :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

type Prod ( NS :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

type Prod ( NS :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

type Prod ( SOP :: (k -> Type ) -> [[k]] -> Type ) = POP :: (k -> Type ) -> [[k]] -> Type
type Prod ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

type Prod ( NP :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

type Prod ( POP :: (k -> Type ) -> [[k]] -> Type ) = POP :: (k -> Type ) -> [[k]] -> Type
type Prod ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

type Prod ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

type Prod ( OptNP empty :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( Telescope g :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

type Prod ( Telescope g :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod ( Mismatch f :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type Prod ( Mismatch f :: (k -> Type ) -> [k] -> Type ) = NP :: (k -> Type ) -> [k] -> Type
type Prod HardForkState Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

class ( Prod ( Prod h) ~ Prod h, HPure ( Prod h)) => HAp (h :: (k -> Type ) -> l -> Type ) where Source #

A generalization of <*> .

Methods

hap :: forall (f :: k -> Type ) (g :: k -> Type ) (xs :: l). Prod h (f -.-> g) xs -> h f xs -> h g xs Source #

Corresponds to <*> .

For products ( NP ) as well as products of products ( POP ), the correspondence is rather direct. We combine a structure containing (lifted) functions and a compatible structure containing corresponding arguments into a compatible structure containing results.

The same combinator can also be used to combine a product structure of functions with a sum structure of arguments, which then results in another sum structure of results. The sum structure determines which part of the product structure will be used.

Instances:

hap, ap_NP  :: NP  (f -.-> g) xs  -> NP  f xs  -> NP  g xs
hap, ap_NS  :: NP  (f -.-> g) xs  -> NS  f xs  -> NS  g xs
hap, ap_POP :: POP (f -.-> g) xss -> POP f xss -> POP g xss
hap, ap_SOP :: POP (f -.-> g) xss -> SOP f xss -> SOP g xss

Instances

Instances details
HAp ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs Source #

HAp ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs Source #

HAp ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod SimpleTelescope (f -.-> g) xs -> SimpleTelescope f xs -> SimpleTelescope g xs Source #

HAp ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs Source #

HAp ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs Source #

HAp ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs Source #

HAp ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod POP (f -.-> g) xs -> POP f xs -> POP g xs Source #

HAp ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

Methods

hap :: forall (f :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod ( OptNP empty) (f -.-> g) xs -> OptNP empty f xs -> OptNP empty g xs Source #

HAp ( Telescope g :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hap :: forall (f :: k0 -> Type ) (g0 :: k0 -> Type ) (xs :: l). Prod ( Telescope g) (f -.-> g0) xs -> Telescope g f xs -> Telescope g g0 xs Source #

HAp ( Mismatch f :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

Methods

hap :: forall (f0 :: k0 -> Type ) (g :: k0 -> Type ) (xs :: l). Prod ( Mismatch f) (f0 -.-> g) xs -> Mismatch f f0 xs -> Mismatch f g xs Source #

HAp HardForkState Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

hap :: forall (f :: k -> Type ) (g :: k -> Type ) (xs :: l). Prod HardForkState (f -.-> g) xs -> HardForkState f xs -> HardForkState g xs Source #

type family CollapseTo (h :: (k -> Type ) -> l -> Type ) x Source #

Maps products to lists, and sums to identities.

Instances

Instances details
type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a Source #
Instance details

Defined in Data.SOP.Strict

type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a = [a]
type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a Source #
Instance details

Defined in Data.SOP.Strict

type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a = a
type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a
Instance details

Defined in Data.SOP.NS

type CollapseTo ( NS :: (k -> Type ) -> [k] -> Type ) a = a
type CollapseTo ( SOP :: (k -> Type ) -> [[k]] -> Type ) a
Instance details

Defined in Data.SOP.NS

type CollapseTo ( SOP :: (k -> Type ) -> [[k]] -> Type ) a = [a]
type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a
Instance details

Defined in Data.SOP.NP

type CollapseTo ( NP :: (k -> Type ) -> [k] -> Type ) a = [a]
type CollapseTo ( POP :: (k -> Type ) -> [[k]] -> Type ) a
Instance details

Defined in Data.SOP.NP

type CollapseTo ( POP :: (k -> Type ) -> [[k]] -> Type ) a = [[a]]
type CollapseTo ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) a Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

type CollapseTo ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) a = [a]
type CollapseTo HardForkState a Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

class HCollapse (h :: (k -> Type ) -> l -> Type ) where Source #

A class for collapsing a heterogeneous structure into a homogeneous one.

Methods

hcollapse :: forall (xs :: l) a. SListIN h xs => h ( K a :: k -> Type ) xs -> CollapseTo h a Source #

Collapse a heterogeneous structure with homogeneous elements into a homogeneous structure.

If a heterogeneous structure is instantiated to the constant functor K , then it is in fact homogeneous. This function maps such a value to a simpler Haskell datatype reflecting that. An NS ( K a) contains a single a , and an NP ( K a) contains a list of a s.

Instances:

hcollapse, collapse_NP  :: NP  (K a) xs  ->  [a]
hcollapse, collapse_NS  :: NS  (K a) xs  ->   a
hcollapse, collapse_POP :: POP (K a) xss -> [[a]]
hcollapse, collapse_SOP :: SOP (K a) xss ->  [a]

Instances

Instances details
HCollapse ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP ( K a) xs -> CollapseTo NP a Source #

HCollapse ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS ( K a) xs -> CollapseTo NS a Source #

HCollapse ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

HCollapse ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN SOP xs => SOP ( K a) xs -> CollapseTo SOP a Source #

HCollapse ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS ( K a) xs -> CollapseTo NS a Source #

HCollapse ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN POP xs => POP ( K a) xs -> CollapseTo POP a Source #

HCollapse ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP ( K a) xs -> CollapseTo NP a Source #

HCollapse HardForkState Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

class HTraverse_ (h :: (k -> Type ) -> l -> Type ) where Source #

A generalization of traverse_ or foldMap .

Since: sop-core-0.3.2.0

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN h c xs, Applicative g) => proxy c -> ( forall (a :: k). c a => f a -> g ()) -> h f xs -> g () Source #

Corresponds to traverse_ .

Instances:

hctraverse_, ctraverse__NP  :: (All  c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> NP  f xs  -> g ()
hctraverse_, ctraverse__NS  :: (All2 c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> NS  f xs  -> g ()
hctraverse_, ctraverse__POP :: (All  c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> POP f xss -> g ()
hctraverse_, ctraverse__SOP :: (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> SOP f xss -> g ()

Since: sop-core-0.3.2.0

htraverse_ :: forall (xs :: l) g f. ( SListIN h xs, Applicative g) => ( forall (a :: k). f a -> g ()) -> h f xs -> g () Source #

Unconstrained version of hctraverse_ .

Instances:

traverse_, traverse__NP  :: (SListI  xs , Applicative g) => (forall a. f a -> g ()) -> NP  f xs  -> g ()
traverse_, traverse__NS  :: (SListI  xs , Applicative g) => (forall a. f a -> g ()) -> NS  f xs  -> g ()
traverse_, traverse__POP :: (SListI2 xss, Applicative g) => (forall a. f a -> g ()) -> POP f xss -> g ()
traverse_, traverse__SOP :: (SListI2 xss, Applicative g) => (forall a. f a -> g ()) -> SOP f xss -> g ()

Since: sop-core-0.3.2.0

Instances

Instances details
HTraverse_ ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source #

HTraverse_ ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN SimpleTelescope c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> SimpleTelescope f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN SimpleTelescope xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> SimpleTelescope f xs -> g () Source #

HTraverse_ ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN SOP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN SOP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> SOP f xs -> g () Source #

HTraverse_ ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN NS c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN NS xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> NS f xs -> g () Source #

HTraverse_ ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN POP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN POP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> POP f xs -> g () Source #

HTraverse_ ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () Source #

htraverse_ :: forall (xs :: l) g f. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g ()) -> NP f xs -> g () Source #

HTraverse_ ( Telescope g :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hctraverse_ :: forall c (xs :: l) g0 proxy f. ( AllN ( Telescope g) c xs, Applicative g0) => proxy c -> ( forall (a :: k0). c a => f a -> g0 ()) -> Telescope g f xs -> g0 () Source #

htraverse_ :: forall (xs :: l) g0 f. ( SListIN ( Telescope g) xs, Applicative g0) => ( forall (a :: k0). f a -> g0 ()) -> Telescope g f xs -> g0 () Source #

class HAp h => HSequence (h :: (k -> Type ) -> l -> Type ) where Source #

A generalization of sequenceA .

Methods

hsequence' :: forall (xs :: l) f (g :: k -> Type ). ( SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs) Source #

Corresponds to sequenceA .

Lifts an applicative functor out of a structure.

Instances:

hsequence', sequence'_NP  :: (SListI  xs , Applicative f) => NP  (f :.: g) xs  -> f (NP  g xs )
hsequence', sequence'_NS  :: (SListI  xs , Applicative f) => NS  (f :.: g) xs  -> f (NS  g xs )
hsequence', sequence'_POP :: (SListI2 xss, Applicative f) => POP (f :.: g) xss -> f (POP g xss)
hsequence', sequence'_SOP :: (SListI2 xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss)

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN h c xs, Applicative g) => proxy c -> ( forall (a :: k). c a => f a -> g (f' a)) -> h f xs -> g (h f' xs) Source #

Corresponds to traverse .

Instances:

hctraverse', ctraverse'_NP  :: (All  c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> NP  f xs  -> g (NP  f' xs )
hctraverse', ctraverse'_NS  :: (All2 c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> NS  f xs  -> g (NS  f' xs )
hctraverse', ctraverse'_POP :: (All  c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
hctraverse', ctraverse'_SOP :: (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss)

Since: sop-core-0.3.2.0

htraverse' :: forall (xs :: l) g f f'. ( SListIN h xs, Applicative g) => ( forall (a :: k). f a -> g (f' a)) -> h f xs -> g (h f' xs) Source #

Unconstrained variant of hctraverse `.

Instances:

htraverse', traverse'_NP  :: (SListI  xs , Applicative g) => (forall a. c a => f a -> g (f' a)) -> NP  f xs  -> g (NP  f' xs )
htraverse', traverse'_NS  :: (SListI2 xs , Applicative g) => (forall a. c a => f a -> g (f' a)) -> NS  f xs  -> g (NS  f' xs )
htraverse', traverse'_POP :: (SListI  xss, Applicative g) => (forall a. c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
htraverse', traverse'_SOP :: (SListI2 xss, Applicative g) => (forall a. c a => f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss)

Since: sop-core-0.3.2.0

Instances

Instances details
HSequence ( NP :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f ( NP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

HSequence ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f ( NS g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NS c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NS xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

HSequence ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN SimpleTelescope xs, Applicative f) => SimpleTelescope (f :.: g) xs -> f ( SimpleTelescope g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN SimpleTelescope c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> SimpleTelescope f xs -> g ( SimpleTelescope f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN SimpleTelescope xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> SimpleTelescope f xs -> g ( SimpleTelescope f' xs) Source #

HSequence ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f ( SOP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN SOP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g ( SOP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN SOP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g ( SOP f' xs) Source #

HSequence ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f ( NS g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NS c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NS xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g ( NS f' xs) Source #

HSequence ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f ( POP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN POP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g ( POP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN POP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g ( POP f' xs) Source #

HSequence ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f ( NP g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN NP c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN NP xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g ( NP f' xs) Source #

HSequence ( OptNP empty :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type ). ( SListIN ( OptNP empty) xs, Applicative f) => OptNP empty (f :.: g) xs -> f ( OptNP empty g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN ( OptNP empty) c xs, Applicative g) => proxy c -> ( forall (a :: k0). c a => f a -> g (f' a)) -> OptNP empty f xs -> g ( OptNP empty f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN ( OptNP empty) xs, Applicative g) => ( forall (a :: k0). f a -> g (f' a)) -> OptNP empty f xs -> g ( OptNP empty f' xs) Source #

HSequence ( Telescope g :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

Methods

hsequence' :: forall (xs :: l) f (g0 :: k0 -> Type ). ( SListIN ( Telescope g) xs, Applicative f) => Telescope g (f :.: g0) xs -> f ( Telescope g g0 xs) Source #

hctraverse' :: forall c (xs :: l) g0 proxy f f'. ( AllN ( Telescope g) c xs, Applicative g0) => proxy c -> ( forall (a :: k0). c a => f a -> g0 (f' a)) -> Telescope g f xs -> g0 ( Telescope g f' xs) Source #

htraverse' :: forall (xs :: l) g0 f f'. ( SListIN ( Telescope g) xs, Applicative g0) => ( forall (a :: k0). f a -> g0 (f' a)) -> Telescope g f xs -> g0 ( Telescope g f' xs) Source #

HSequence HardForkState Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

Methods

hsequence' :: forall (xs :: l) f (g :: k -> Type ). ( SListIN HardForkState xs, Applicative f) => HardForkState (f :.: g) xs -> f ( HardForkState g xs) Source #

hctraverse' :: forall c (xs :: l) g proxy f f'. ( AllN HardForkState c xs, Applicative g) => proxy c -> ( forall (a :: k). c a => f a -> g (f' a)) -> HardForkState f xs -> g ( HardForkState f' xs) Source #

htraverse' :: forall (xs :: l) g f f'. ( SListIN HardForkState xs, Applicative g) => ( forall (a :: k). f a -> g (f' a)) -> HardForkState f xs -> g ( HardForkState f' xs) Source #

class HIndex (h :: (k -> Type ) -> l -> Type ) where Source #

A class for determining which choice in a sum-like structure a value represents.

Methods

hindex :: forall (f :: k -> Type ) (xs :: l). h f xs -> Int Source #

If h is a sum-like structure representing a choice between n different options, and x is a value of type h f xs , then hindex x returns a number between 0 and n - 1 representing the index of the choice made by x .

Instances:

hindex, index_NS  :: NS  f xs -> Int
hindex, index_SOP :: SOP f xs -> Int

Examples:

>>> hindex (S (S (Z (I False))))
2
>>> hindex (Z (K ()))
0
>>> hindex (SOP (S (Z (I True :* I 'x' :* Nil))))
1

Since: sop-core-0.2.4.0

Instances

Instances details
HIndex ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type ) (xs :: l). SOP f xs -> Int Source #

HIndex ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type ) (xs :: l). NS f xs -> Int Source #

type family UnProd (h :: (k -> Type ) -> l -> Type ) :: (k -> Type ) -> l -> Type Source #

Maps a structure containing products to the corresponding sum structure.

Since: sop-core-0.2.4.0

Instances

Instances details
type UnProd ( NP :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

type UnProd ( NP :: (k -> Type ) -> [k] -> Type ) = NS :: (k -> Type ) -> [k] -> Type
type UnProd ( POP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

type UnProd ( POP :: (k -> Type ) -> [[k]] -> Type ) = SOP :: (k -> Type ) -> [[k]] -> Type

class UnProd ( Prod h) ~ h => HApInjs (h :: (k -> Type ) -> l -> Type ) where Source #

A class for applying all injections corresponding to a sum-like structure to a table containing suitable arguments.

Methods

hapInjs :: forall (xs :: l) (f :: k -> Type ). SListIN h xs => Prod h f xs -> [h f xs] Source #

For a given table (product-like structure), produce a list where each element corresponds to the application of an injection function into the corresponding sum-like structure.

Instances:

hapInjs, apInjs_NP  :: SListI  xs  => NP  f xs -> [NS  f xs ]
hapInjs, apInjs_SOP :: SListI2 xss => POP f xs -> [SOP f xss]

Examples:

>>> hapInjs (I 'x' :* I True :* I 2 :* Nil) :: [NS I '[Char, Bool, Int]]
[Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]
>>> hapInjs (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil)) :: [SOP I '[ '[Char], '[Bool, Int]]]
[SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]

Unfortunately the type-signatures are required in GHC-7.10 and older.

Since: sop-core-0.2.4.0

Instances

Instances details
HApInjs ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type ). SListIN SOP xs => Prod SOP f xs -> [ SOP f xs] Source #

HApInjs ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type ). SListIN NS xs => Prod NS f xs -> [ NS f xs] Source #

class HExpand (h :: (k -> Type ) -> l -> Type ) where Source #

A class for expanding sum structures into corresponding product structures, filling in the slots not targeted by the sum with default values.

Since: sop-core-0.2.5.0

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod h) xs => ( forall (x :: k). f x) -> h f xs -> Prod h f xs Source #

Expand a given sum structure into a corresponding product structure by placing the value contained in the sum into the corresponding position in the product, and using the given default value for all other positions.

Instances:

hexpand, expand_NS  :: SListI xs   => (forall x . f x) -> NS  f xs  -> NP  f xs
hexpand, expand_SOP :: SListI2 xss => (forall x . f x) -> SOP f xss -> POP f xss

Examples:

>>> hexpand Nothing (S (Z (Just 3))) :: NP Maybe '[Char, Int, Bool]
Nothing :* Just 3 :* Nothing :* Nil
>>> hexpand [] (SOP (S (Z ([1,2] :* "xyz" :* Nil)))) :: POP [] '[ '[Bool], '[Int, Char] ]
POP (([] :* Nil) :* ([1,2] :* "xyz" :* Nil) :* Nil)

Since: sop-core-0.2.5.0

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod h) c xs => proxy c -> ( forall (x :: k). c x => f x) -> h f xs -> Prod h f xs Source #

Variant of hexpand that allows passing a constrained default.

Instances:

hcexpand, cexpand_NS  :: All  c xs  => proxy c -> (forall x . c x => f x) -> NS  f xs  -> NP  f xs
hcexpand, cexpand_SOP :: All2 c xss => proxy c -> (forall x . c x => f x) -> SOP f xss -> POP f xss

Examples:

>>> hcexpand (Proxy :: Proxy Bounded) (I minBound) (S (Z (I 20))) :: NP I '[Bool, Int, Ordering]
I False :* I 20 :* I LT :* Nil
>>> hcexpand (Proxy :: Proxy Num) (I 0) (SOP (S (Z (I 1 :* I 2 :* Nil)))) :: POP I '[ '[Double], '[Int, Int] ]
POP ((I 0.0 :* Nil) :* (I 1 :* I 2 :* Nil) :* Nil)

Since: sop-core-0.2.5.0

Instances

Instances details
HExpand ( NS :: (k -> Type ) -> [k] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod NS ) xs => ( forall (x :: k0). f x) -> NS f xs -> Prod NS f xs Source #

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod NS ) c xs => proxy c -> ( forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs Source #

HExpand ( SOP :: (k -> Type ) -> [[k]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod SOP ) xs => ( forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs Source #

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod SOP ) c xs => proxy c -> ( forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs Source #

HExpand ( NS :: (k -> Type ) -> [k] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN ( Prod NS ) xs => ( forall (x :: k0). f x) -> NS f xs -> Prod NS f xs Source #

hcexpand :: forall c (xs :: l) proxy f. AllN ( Prod NS ) c xs => proxy c -> ( forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs Source #

class (( Same h1 :: (k2 -> Type ) -> l2 -> Type ) ~ h2, ( Same h2 :: (k1 -> Type ) -> l1 -> Type ) ~ h1) => HTrans (h1 :: (k1 -> Type ) -> l1 -> Type ) (h2 :: (k2 -> Type ) -> l2 -> Type ) where Source #

A class for transforming structures into related structures with a different index list, as long as the index lists have the same shape and the elements and interpretation functions are suitably related.

Since: sop-core-0.3.1.0

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod h1) c xs ys => proxy c -> ( forall (x :: k1) (y :: k2). c x y => f x -> g y) -> h1 f xs -> h2 g ys Source #

Transform a structure into a related structure given a conversion function for the elements.

Since: sop-core-0.3.1.0

hcoerce :: forall (f :: k1 -> Type ) (g :: k2 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod h1) ( LiftedCoercible f g) xs ys => h1 f xs -> h2 g ys Source #

Safely coerce a structure into a representationally equal structure.

This is a special case of htrans , but can be implemented more efficiently; for example in terms of unsafeCoerce .

Examples:

>>> hcoerce (I (Just LT) :* I (Just 'x') :* I (Just True) :* Nil) :: NP Maybe '[Ordering, Char, Bool]
Just LT :* Just 'x' :* Just True :* Nil
>>> hcoerce (SOP (Z (K True :* K False :* Nil))) :: SOP I '[ '[Bool, Bool], '[Bool] ]
SOP (Z (I True :* I False :* Nil))

Since: sop-core-0.3.1.0

Instances

Instances details
HTrans ( NP :: (k1 -> Type ) -> [k1] -> Type ) ( NP :: (k2 -> Type ) -> [k2] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NP ) ( LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source #

HTrans ( NS :: (k1 -> Type ) -> [k1] -> Type ) ( NS :: (k2 -> Type ) -> [k2] -> Type ) Source #
Instance details

Defined in Data.SOP.Strict

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NS ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NS ) ( LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source #

HTrans ( SOP :: (k1 -> Type ) -> [[k1]] -> Type ) ( SOP :: (k2 -> Type ) -> [[k2]] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod SOP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod SOP ) ( LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys Source #

HTrans ( NS :: (k1 -> Type ) -> [k1] -> Type ) ( NS :: (k2 -> Type ) -> [k2] -> Type )
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NS ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NS ) ( LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source #

HTrans ( POP :: (k1 -> Type ) -> [[k1]] -> Type ) ( POP :: (k2 -> Type ) -> [[k2]] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod POP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod POP ) ( LiftedCoercible f g) xs ys => POP f xs -> POP g ys Source #

HTrans ( NP :: (k1 -> Type ) -> [k1] -> Type ) ( NP :: (k2 -> Type ) -> [k2] -> Type )
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN ( Prod NP ) c xs ys => proxy c -> ( forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys Source #

hcoerce :: forall (f :: k10 -> Type ) (g :: k20 -> Type ) (xs :: l1) (ys :: l2). AllZipN ( Prod NP ) ( LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source #

ccase_SList :: forall k c (xs :: [k]) proxy r. All c xs => proxy c -> r ('[] :: [k]) -> ( forall (y :: k) (ys :: [k]). (c y, All c ys) => r (y ': ys)) -> r xs Source #

Constrained case distinction on a type-level list.

Since: sop-core-0.4.0.0

class ( AllF c xs, SListI xs) => All (c :: k -> Constraint ) (xs :: [k]) where Source #

Require a constraint for every element of a list.

If you have a datatype that is indexed over a type-level list, then you can use All to indicate that all elements of that type-level list must satisfy a given constraint.

Example: The constraint

All Eq '[ Int, Bool, Char ]

is equivalent to the constraint

(Eq Int, Eq Bool, Eq Char)

Example: A type signature such as

f :: All Eq xs => NP I xs -> ...

means that f can assume that all elements of the n-ary product satisfy Eq .

Note on superclasses: ghc cannot deduce superclasses from All constraints. You might expect the following to compile

class (Eq a) => MyClass a

foo :: (All Eq xs) => NP f xs -> z
foo = [..]

bar :: (All MyClass xs) => NP f xs -> x
bar = foo

but it will fail with an error saying that it was unable to deduce the class constraint AllF Eq xs (or similar) in the definition of bar . In cases like this you can use Dict from Data.SOP.Dict to prove conversions between constraints. See this answer on SO for more details .

Methods

cpara_SList :: proxy c -> r ('[] :: [k]) -> ( forall (y :: k) (ys :: [k]). (c y, All c ys) => r ys -> r (y ': ys)) -> r xs Source #

Constrained paramorphism for a type-level list.

The advantage of writing functions in terms of cpara_SList is that they are then typically not recursive, and can be unfolded statically if the type-level list is statically known.

Since: sop-core-0.4.0.0

Instances

Instances details
All (c :: k -> Constraint ) ('[] :: [k])
Instance details

Defined in Data.SOP.Constraint

Methods

cpara_SList :: proxy c -> r '[] -> ( forall (y :: k0) (ys :: [k0]). (c y, All c ys) => r ys -> r (y ': ys)) -> r '[] Source #

(c x, All c xs) => All (c :: a -> Constraint ) (x ': xs :: [a])
Instance details

Defined in Data.SOP.Constraint

Methods

cpara_SList :: proxy c -> r '[] -> ( forall (y :: k) (ys :: [k]). (c y, All c ys) => r ys -> r (y ': ys)) -> r (x ': xs) Source #

type SListI2 = All ( SListI :: [k] -> Constraint ) Source #

Require a singleton for every inner list in a list of lists.

type SListI = All ( Top :: k -> Constraint ) Source #

Implicit singleton list.

A singleton list can be used to reveal the structure of a type-level list argument that the function is quantified over.

Since 0.4.0.0, this is now defined in terms of All . A singleton list provides a witness for a type-level list where the elements need not satisfy any additional constraints.

Since: sop-core-0.4.0.0

type All2 (c :: k -> Constraint ) = All ( All c) Source #

Require a constraint for every element of a list of lists.

If you have a datatype that is indexed over a type-level list of lists, then you can use All2 to indicate that all elements of the inner lists must satisfy a given constraint.

Example: The constraint

All2 Eq '[ '[ Int ], '[ Bool, Char ] ]

is equivalent to the constraint

(Eq Int, Eq Bool, Eq Char)

Example: A type signature such as

f :: All2 Eq xss => SOP I xs -> ...

means that f can assume that all elements of the sum of product satisfy Eq .

Since 0.4.0.0, this is merely a synonym for 'All (All c)'.

Since: sop-core-0.4.0.0

class ( SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint ) (xs :: [a]) (ys :: [b]) Source #

Require a constraint pointwise for every pair of elements from two lists.

Example: The constraint

AllZip (~) '[ Int, Bool, Char ] '[ a, b, c ]

is equivalent to the constraint

(Int ~ a, Bool ~ b, Char ~ c)

Since: sop-core-0.3.1.0

Instances

Instances details
( SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint ) (xs :: [a]) (ys :: [b])
Instance details

Defined in Data.SOP.Constraint

type family SameShapeAs (xs :: [a]) (ys :: [b]) where ... Source #

Type family that forces a type-level list to be of the same shape as the given type-level list.

Since 0.5.0.0, this only tests the top-level structure of the list, and is intended to be used in conjunction with a separate construct (such as the AllZip , AllZipF combination to tie the recursive knot). The reason is that making SameShapeAs directly recursive leads to quadratic compile times.

The main use of this constraint is to help type inference to learn something about otherwise unknown type-level lists.

Since: sop-core-0.5.0.0

Equations

SameShapeAs ('[] :: [a]) (ys :: [b]) = ys ~ ('[] :: [b])
SameShapeAs (x ': xs :: [a1]) (ys :: [a2]) = ys ~ ( Head ys ': Tail ys)

class Coercible (f x) (g y) => LiftedCoercible (f :: k -> k1) (g :: k2 -> k1) (x :: k) (y :: k2) Source #

The constraint LiftedCoercible f g x y is equivalent to Coercible (f x) (g y) .

Since: sop-core-0.3.1.0

Instances

Instances details
Coercible (f x) (g y) => LiftedCoercible (f :: k1 -> k2) (g :: k3 -> k2) (x :: k1) (y :: k3)
Instance details

Defined in Data.SOP.Constraint

class ( AllZipF ( AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint ) (xss :: [[a]]) (yss :: [[b]]) Source #

Require a constraint pointwise for every pair of elements from two lists of lists.

Instances

Instances details
( AllZipF ( AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint ) (xss :: [[a]]) (yss :: [[b]])
Instance details

Defined in Data.SOP.Constraint

class f (g x) => Compose (f :: k -> Constraint ) (g :: k1 -> k) (x :: k1) infixr 9 Source #

Composition of constraints.

Note that the result of the composition must be a constraint, and therefore, in Compose f g , the kind of f is k -> Constraint . The kind of g , however, is l -> k and can thus be a normal type constructor.

A typical use case is in connection with All on an NP or an NS . For example, in order to denote that all elements on an NP f xs satisfy Show , we can say All ( Compose Show f) xs .

Since: sop-core-0.2

Instances

Instances details
f (g x) => Compose (f :: k1 -> Constraint ) (g :: k2 -> k1) (x :: k2)
Instance details

Defined in Data.SOP.Constraint

class (f x, g x) => And (f :: k -> Constraint ) (g :: k -> Constraint ) (x :: k) infixl 7 Source #

Pairing of constraints.

Since: sop-core-0.2

Instances

Instances details
(f x, g x) => And (f :: k -> Constraint ) (g :: k -> Constraint ) (x :: k)
Instance details

Defined in Data.SOP.Constraint

class Top (x :: k) Source #

A constraint that can always be satisfied.

Since: sop-core-0.2

Instances

Instances details
Top (x :: k)
Instance details

Defined in Data.SOP.Constraint

type family AllN (h :: (k -> Type ) -> l -> Type ) (c :: k -> Constraint ) :: l -> Constraint Source #

A generalization of All and All2 .

The family AllN expands to All or All2 depending on whether the argument is indexed by a list or a list of lists.

Instances

Instances details
type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NS

type AllN ( NS :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( SOP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NS

type AllN ( SOP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint ) = All2 c
type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: k -> Constraint ) = All2 c
type AllN ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

type AllN ( SimpleTelescope :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( OptNP empty :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.Util.OptNP

type AllN ( OptNP empty :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( Telescope g :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Telescope

type AllN ( Telescope g :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Util.Match

type AllN ( Mismatch f :: (k -> Type ) -> [k] -> Type ) (c :: k -> Constraint ) = All c
type AllN HardForkState (c :: Type -> Constraint ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type family AllZipN (h :: (k -> Type ) -> l -> Type ) (c :: k1 -> k2 -> Constraint ) :: l1 -> l2 -> Constraint Source #

A generalization of AllZip and AllZip2 .

The family AllZipN expands to AllZip or AllZip2 depending on whther the argument is indexed by a list or a list of lists.

Instances

Instances details
type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint ) Source #
Instance details

Defined in Data.SOP.Strict

type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint ) = AllZip c
type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllZipN ( NP :: (k -> Type ) -> [k] -> Type ) (c :: a -> b -> Constraint ) = AllZip c
type AllZipN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: a -> b -> Constraint )
Instance details

Defined in Data.SOP.NP

type AllZipN ( POP :: (k -> Type ) -> [[k]] -> Type ) (c :: a -> b -> Constraint ) = AllZip2 c

mapKKK :: forall k1 k2 k3 a b c (d :: k1) (e :: k2) (f :: k3). (a -> b -> c) -> K a d -> K b e -> K c f Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapKKI :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> K b e -> I c Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapKIK :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> I b -> K c e Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapKII :: forall k a b c (d :: k). (a -> b -> c) -> K a d -> I b -> I c Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapIKK :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> I a -> K b d -> K c e Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapIKI :: forall k a b c (d :: k). (a -> b -> c) -> I a -> K b d -> I c Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapIIK :: forall k a b c (d :: k). (a -> b -> c) -> I a -> I b -> K c d Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapIII :: (a -> b -> c) -> I a -> I b -> I c Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapKK :: forall k1 k2 a b (c :: k1) (d :: k2). (a -> b) -> K a c -> K b d Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapKI :: forall k a b (c :: k). (a -> b) -> K a c -> I b Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapIK :: forall k a b (c :: k). (a -> b) -> I a -> K b c Source #

Lift the given function.

Since: sop-core-0.2.5.0

mapII :: (a -> b) -> I a -> I b Source #

Lift the given function.

Since: sop-core-0.2.5.0

unComp :: forall l k f (g :: k -> l) (p :: k). (f :.: g) p -> f (g p) Source #

Extract the contents of a Comp value.

unI :: I a -> a Source #

Extract the contents of an I value.

unK :: forall k a (b :: k). K a b -> a Source #

Extract the contents of a K value.

newtype K a (b :: k) Source #

The constant type functor.

Like Constant , but kind-polymorphic in its second argument and with a shorter name.

Constructors

K a

Instances

Instances details
Show ( Ticked a) => Show ( Ticked ( K a x)) Source #
Instance details

Defined in Ouroboros.Consensus.Ticked

( SListI xs, Show ( Ticked a)) => Show ( Ticked ( HardForkLedgerView_ ( K a :: Type -> Type ) xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Eq2 ( K :: Type -> Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq2 :: (a -> b -> Bool ) -> (c -> d -> Bool ) -> K a c -> K b d -> Bool Source #

Ord2 ( K :: Type -> Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare2 :: (a -> b -> Ordering ) -> (c -> d -> Ordering ) -> K a c -> K b d -> Ordering Source #

Read2 ( K :: Type -> Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Show2 ( K :: Type -> Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec2 :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> ( Int -> b -> ShowS ) -> ([b] -> ShowS ) -> Int -> K a b -> ShowS Source #

liftShowList2 :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> ( Int -> b -> ShowS ) -> ([b] -> ShowS ) -> [ K a b] -> ShowS Source #

NFData2 ( K :: Type -> Type -> Type )

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> K a b -> () Source #

Functor ( K a :: Type -> Type )
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a0 -> b) -> K a a0 -> K a b Source #

(<$) :: a0 -> K a b -> K a a0 Source #

( SListI xs, Show a) => Show ( HardForkLedgerView_ ( K a :: Type -> Type ) xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Monoid a => Applicative ( K a :: Type -> Type )
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a0 -> K a a0 Source #

(<*>) :: K a (a0 -> b) -> K a a0 -> K a b Source #

liftA2 :: (a0 -> b -> c) -> K a a0 -> K a b -> K a c Source #

(*>) :: K a a0 -> K a b -> K a b Source #

(<*) :: K a a0 -> K a b -> K a a0 Source #

Foldable ( K a :: Type -> Type )
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => K a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> K a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> K a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> K a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 Source #

toList :: K a a0 -> [a0] Source #

null :: K a a0 -> Bool Source #

length :: K a a0 -> Int Source #

elem :: Eq a0 => a0 -> K a a0 -> Bool Source #

maximum :: Ord a0 => K a a0 -> a0 Source #

minimum :: Ord a0 => K a a0 -> a0 Source #

sum :: Num a0 => K a a0 -> a0 Source #

product :: Num a0 => K a a0 -> a0 Source #

Traversable ( K a :: Type -> Type )
Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a0 -> f b) -> K a a0 -> f ( K a b) Source #

sequenceA :: Applicative f => K a (f a0) -> f ( K a a0) Source #

mapM :: Monad m => (a0 -> m b) -> K a a0 -> m ( K a b) Source #

sequence :: Monad m => K a (m a0) -> m ( K a a0) Source #

Eq a => Eq1 ( K a :: Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a0 -> b -> Bool ) -> K a a0 -> K a b -> Bool Source #

Ord a => Ord1 ( K a :: Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a0 -> b -> Ordering ) -> K a a0 -> K a b -> Ordering Source #

Read a => Read1 ( K a :: Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Show a => Show1 ( K a :: Type -> Type )

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: ( Int -> a0 -> ShowS ) -> ([a0] -> ShowS ) -> Int -> K a a0 -> ShowS Source #

liftShowList :: ( Int -> a0 -> ShowS ) -> ([a0] -> ShowS ) -> [ K a a0] -> ShowS Source #

NFData a => NFData1 ( K a :: Type -> Type )

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a0 -> ()) -> K a a0 -> () Source #

Eq a => Eq ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

Ord a => Ord ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

Read a => Read ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

Show a => Show ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

Generic ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep ( K a b) :: Type -> Type Source #

Semigroup a => Semigroup ( K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Monoid a => Monoid ( K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

NFData a => NFData ( K a b)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: K a b -> () Source #

NoThunks a => NoThunks ( K a b) Source #
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

type Rep ( K a b)
Instance details

Defined in Data.SOP.BasicFunctors

type Rep ( K a b) = D1 (' MetaData "K" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-AIuTztJH91BC7RnRhk6DyL" ' True ) ( C1 (' MetaCons "K" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 a)))
newtype Ticked ( K a x) Source #
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype I a Source #

The identity type functor.

Like Identity , but with a shorter name.

Constructors

I a

Instances

Instances details
Monad I
Instance details

Defined in Data.SOP.BasicFunctors

Functor I
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> I a -> I b Source #

(<$) :: a -> I b -> I a Source #

Applicative I
Instance details

Defined in Data.SOP.BasicFunctors

Foldable I
Instance details

Defined in Data.SOP.BasicFunctors

Traversable I
Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a -> f b) -> I a -> f ( I b) Source #

sequenceA :: Applicative f => I (f a) -> f ( I a) Source #

mapM :: Monad m => (a -> m b) -> I a -> m ( I b) Source #

sequence :: Monad m => I (m a) -> m ( I a) Source #

Eq1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool ) -> I a -> I b -> Bool Source #

Ord1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Read1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Show1 I

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

NFData1 I

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> I a -> () Source #

Isomorphic I Source #
Instance details

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

Inject I Source #
Instance details

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

DecodeDisk blk blk => DecodeDisk blk ( I blk) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDisk :: CodecConfig blk -> forall s. Decoder s ( I blk) Source #

( DecodeDiskDepIx f blk, DecodeDiskDep f blk) => DecodeDisk blk ( DepPair (f blk)) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDisk :: CodecConfig blk -> forall s. Decoder s ( DepPair (f blk)) Source #

EncodeDisk blk blk => EncodeDisk blk ( I blk) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

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

Defined in Ouroboros.Consensus.Storage.Serialisation

SerialiseNodeToClient blk blk => SerialiseNodeToClient blk ( I blk) Source #
Instance details

Defined in Ouroboros.Consensus.Node.Serialisation

SerialiseNodeToNode blk blk => SerialiseNodeToNode blk ( I blk) Source #
Instance details

Defined in Ouroboros.Consensus.Node.Serialisation

Eq a => Eq ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

Ord a => Ord ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

Read a => Read ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

Show a => Show ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

Generic ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep ( I a) :: Type -> Type Source #

Semigroup a => Semigroup ( I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Monoid a => Monoid ( I a)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

NFData a => NFData ( I a)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: I a -> () Source #

Condense a => Condense ( I a) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

type Rep ( I a)
Instance details

Defined in Data.SOP.BasicFunctors

type Rep ( I a) = D1 (' MetaData "I" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-AIuTztJH91BC7RnRhk6DyL" ' True ) ( C1 (' MetaCons "I" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 a)))

newtype ((f :: l -> Type ) :.: (g :: k -> l)) (p :: k) infixr 7 Source #

Composition of functors.

Like Compose , but kind-polymorphic and with a shorter name.

Constructors

Comp (f (g p))

Instances

Instances details
DecodeDisk blk (a -> f blk) => DecodeDisk blk ((((->) a :: Type -> Type ) :.: f) blk) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDisk :: CodecConfig blk -> forall s. Decoder s (((->) a :.: f) blk) Source #

( Functor f, Functor g) => Functor (f :.: g)
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

( Applicative f, Applicative g) => Applicative (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a -> (f :.: g) a Source #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source #

( Foldable f, Foldable g) => Foldable (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => (f :.: g) m -> m Source #

foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m Source #

foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m Source #

foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b Source #

foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b Source #

foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b Source #

foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b Source #

foldr1 :: (a -> a -> a) -> (f :.: g) a -> a Source #

foldl1 :: (a -> a -> a) -> (f :.: g) a -> a Source #

toList :: (f :.: g) a -> [a] Source #

null :: (f :.: g) a -> Bool Source #

length :: (f :.: g) a -> Int Source #

elem :: Eq a => a -> (f :.: g) a -> Bool Source #

maximum :: Ord a => (f :.: g) a -> a Source #

minimum :: Ord a => (f :.: g) a -> a Source #

sum :: Num a => (f :.: g) a -> a Source #

product :: Num a => (f :.: g) a -> a Source #

( Traversable f, Traversable g) => Traversable (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source #

sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) Source #

mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) Source #

sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) Source #

( Eq1 f, Eq1 g) => Eq1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool ) -> (f :.: g) a -> (f :.: g) b -> Bool Source #

( Ord1 f, Ord1 g) => Ord1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering ) -> (f :.: g) a -> (f :.: g) b -> Ordering Source #

( Read1 f, Read1 g) => Read1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

( Show1 f, Show1 g) => Show1 (f :.: g)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> Int -> (f :.: g) a -> ShowS Source #

liftShowList :: ( Int -> a -> ShowS ) -> ([a] -> ShowS ) -> [(f :.: g) a] -> ShowS Source #

( NFData1 f, NFData1 g) => NFData1 (f :.: g)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> (f :.: g) a -> () Source #

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

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

( Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a)
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

(/=) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

( Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a)
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: (f :.: g) a -> (f :.: g) a -> Ordering Source #

(<) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

(<=) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

(>) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

(>=) :: (f :.: g) a -> (f :.: g) a -> Bool Source #

max :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

min :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

( Read1 f, Read1 g, Read a) => Read ((f :.: g) a)
Instance details

Defined in Data.SOP.BasicFunctors

( Show1 f, Show1 g, Show a) => Show ((f :.: g) a)
Instance details

Defined in Data.SOP.BasicFunctors

Show ( Ticked (f a)) => Show (( Ticked :.: f) a) Source #
Instance details

Defined in Ouroboros.Consensus.Ticked

Generic ((f :.: g) p)
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep ((f :.: g) p) :: Type -> Type Source #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x Source #

to :: Rep ((f :.: g) p) x -> (f :.: g) p Source #

Semigroup (f (g x)) => Semigroup ((f :.: g) x)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x Source #

sconcat :: NonEmpty ((f :.: g) x) -> (f :.: g) x Source #

stimes :: Integral b => b -> (f :.: g) x -> (f :.: g) x Source #

Monoid (f (g x)) => Monoid ((f :.: g) x)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: (f :.: g) x Source #

mappend :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x Source #

mconcat :: [(f :.: g) x] -> (f :.: g) x Source #

NFData (f (g a)) => NFData ((f :.: g) a)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: (f :.: g) a -> () Source #

NoThunks ( Ticked (f a)) => NoThunks (( Ticked :.: f) a) Source #
Instance details

Defined in Ouroboros.Consensus.Ticked

type Rep ((f :.: g) p)
Instance details

Defined in Data.SOP.BasicFunctors

type Rep ((f :.: g) p) = D1 (' MetaData ":.:" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-AIuTztJH91BC7RnRhk6DyL" ' True ) ( C1 (' MetaCons "Comp" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 (f (g p)))))