sop-core-0.5.0.1: True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Data.SOP.NS

Contents

Description

n-ary sums (and sums of products)

Synopsis

Datatypes

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

An n-ary sum.

The sum is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of choices in the sum and if the i-th element of the list is of type x, then the i-th choice of the sum is of type f x.

The constructor names are chosen to resemble Peano-style natural numbers, i.e., Z is for "zero", and S is for "successor". Chaining S and Z chooses the corresponding component of the sum.

Examples:

Z         :: f x -> NS f (x ': xs)
S . Z     :: f y -> NS f (x ': y ': xs)
S . S . Z :: f z -> NS f (x ': y ': z ': xs)
...

Note that empty sums (indexed by an empty list) have no non-bottom elements.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the sum becomes a direct generalization of the Either type to arbitrarily many choices. For K a, the result is a homogeneous choice type, where the contents of the type-level list are ignored, but its length specifies the number of options.

In the context of the SOP approach to generic programming, an n-ary sum describes the top-level structure of a datatype, which is a choice between all of its constructors.

Examples:

Z (I 'x')      :: NS I       '[ Char, Bool ]
S (Z (I True)) :: NS I       '[ Char, Bool ]
S (Z (K 1))    :: NS (K Int) '[ Char, Bool ]

Constructors

Z :: f x -> NS f (x ': xs) 
S :: NS f xs -> NS f (x ': xs) 
Instances
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: 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 :: AllZipN (Prod NS) (LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source #

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

Defined in Data.SOP.NS

Methods

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

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

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

Defined in Data.SOP.NS

Methods

hapInjs :: SListIN NS xs => Prod NS f xs -> [NS f xs] Source #

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

Defined in Data.SOP.NS

Methods

hindex :: NS f xs -> Int Source #

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

Defined in Data.SOP.NS

Methods

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

hctraverse' :: (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' :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source #

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

Defined in Data.SOP.NS

Methods

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

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

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

Defined in Data.SOP.NS

Methods

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

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

Defined in Data.SOP.NS

Methods

hap :: Prod NS (f -.-> g) xs -> NS f xs -> NS g xs Source #

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

Defined in Data.SOP.NS

Methods

(==) :: NS f xs -> NS f xs -> Bool #

(/=) :: NS f xs -> NS f xs -> Bool #

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

Defined in Data.SOP.NS

Methods

compare :: NS f xs -> NS f xs -> Ordering #

(<) :: NS f xs -> NS f xs -> Bool #

(<=) :: NS f xs -> NS f xs -> Bool #

(>) :: NS f xs -> NS f xs -> Bool #

(>=) :: NS f xs -> NS f xs -> Bool #

max :: NS f xs -> NS f xs -> NS f xs #

min :: NS f xs -> NS f xs -> NS f xs #

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

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> NS f xs -> ShowS #

show :: NS f xs -> String #

showList :: [NS f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NS f xs) Source #

Since: 0.2.5.0

Instance details

Defined in Data.SOP.NS

Methods

rnf :: NS f xs -> () #

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

Defined in Data.SOP.NS

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.NS

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

Defined in Data.SOP.NS

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

Defined in Data.SOP.NS

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

Defined in Data.SOP.NS

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

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
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) Source # 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: 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 :: AllZipN (Prod SOP) (LiftedCoercible f g) xs ys => SOP f xs -> SOP g ys Source #

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

Defined in Data.SOP.NS

Methods

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

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

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

Defined in Data.SOP.NS

Methods

hapInjs :: SListIN SOP xs => Prod SOP f xs -> [SOP f xs] Source #

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

Defined in Data.SOP.NS

Methods

hindex :: SOP f xs -> Int Source #

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

Defined in Data.SOP.NS

Methods

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

hctraverse' :: (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' :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) Source #

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

Defined in Data.SOP.NS

Methods

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

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

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

Defined in Data.SOP.NS

Methods

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

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

Defined in Data.SOP.NS

Methods

hap :: Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs Source #

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

Defined in Data.SOP.NS

Methods

(==) :: SOP f xss -> SOP f xss -> Bool #

(/=) :: SOP f xss -> SOP f xss -> Bool #

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

Defined in Data.SOP.NS

Methods

compare :: SOP f xss -> SOP f xss -> Ordering #

(<) :: SOP f xss -> SOP f xss -> Bool #

(<=) :: SOP f xss -> SOP f xss -> Bool #

(>) :: SOP f xss -> SOP f xss -> Bool #

(>=) :: SOP f xss -> SOP f xss -> Bool #

max :: SOP f xss -> SOP f xss -> SOP f xss #

min :: SOP f xss -> SOP f xss -> SOP f xss #

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

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> SOP f xss -> ShowS #

show :: SOP f xss -> String #

showList :: [SOP f xss] -> ShowS #

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

Since: 0.2.5.0

Instance details

Defined in Data.SOP.NS

Methods

rnf :: SOP f xss -> () #

type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) Source # 
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) Source # 
Instance details

Defined in Data.SOP.NS

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

Defined in Data.SOP.NS

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

Defined in Data.SOP.NS

type SListIN (SOP :: (k -> Type) -> [[k]] -> Type) = (SListI2 :: [[k]] -> Constraint)
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # 
Instance details

Defined in Data.SOP.NS

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

unSOP :: SOP f xss -> NS (NP f) xss Source #

Unwrap a sum of products.

Constructing sums

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

The type of injections into an n-ary sum.

If you expand the type synonyms and newtypes involved, you get

Injection f xs a = (f -.-> K (NS f xs)) a ~= f a -> K (NS f xs) a ~= f a -> NS f xs

If we pick a to be an element of xs, this indeed corresponds to an injection into the sum.

injections :: forall xs f. SListI xs => NP (Injection f xs) xs Source #

Compute all injections into an n-ary sum.

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

shift :: Injection f xs a -> Injection f (x ': xs) a Source #

Deprecated: Use shiftInjection instead.

Shift an injection.

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

shiftInjection :: Injection f xs a -> Injection f (x ': xs) a Source #

Shift an injection.

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

apInjs_NP :: 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)))]

apInjs'_NP :: SListI xs => NP f xs -> NP (K (NS f xs)) xs Source #

apInjs_NP without hcollapse.

>>> apInjs'_NP (I 'x' :* I True :* I 2 :* Nil)
K (Z (I 'x')) :* K (S (Z (I True))) :* K (S (S (Z (I 2)))) :* Nil

Since: 0.2.5.0

apInjs_POP :: 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'_POP :: SListI xss => POP f xss -> NP (K (SOP f xss)) xss Source #

apInjs_POP without hcollapse.

Example:

>>> apInjs'_POP (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil))
K (SOP (Z (I 'x' :* Nil))) :* K (SOP (S (Z (I True :* I 2 :* Nil)))) :* Nil

Since: 0.2.5.0

Destructing sums

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

Extract the payload from a unary sum.

For larger sums, this function would be partial, so it is only provided with a rather restrictive type.

Example:

>>> unZ (Z (I 'x'))
I 'x'

Since: 0.2.2.0

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

Obtain the index from an n-ary sum.

An n-nary sum represents a choice between n different options. This function returns an integer between 0 and n - 1 indicating the option chosen by the given value.

Examples:

>>> index_NS (S (S (Z (I False))))
2
>>> index_NS (Z (K ()))
0

Since: 0.2.4.0

index_SOP :: SOP f xs -> Int Source #

Obtain the index from an n-ary sum of products.

An n-nary sum represents a choice between n different options. This function returns an integer between 0 and n - 1 indicating the option chosen by the given value.

Specification:

index_SOP = index_NS . unSOP

Example:

>>> index_SOP (SOP (S (Z (I True :* I 'x' :* Nil))))
1

Since: 0.2.4.0

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

The type of ejections from an n-ary sum.

An ejection is the pattern matching function for one part of the n-ary sum.

It is the opposite of an Injection.

Since: 0.5.0.0

ejections :: forall xs f. SListI xs => NP (Ejection f xs) xs Source #

Compute all ejections from an n-ary sum.

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

Since: 0.5.0.0

shiftEjection :: forall f x xs a. Ejection f xs a -> Ejection f (x ': xs) a Source #

Since: 0.5.0.0

Application

ap_NS :: NP (f -.-> g) xs -> NS f xs -> NS g xs Source #

Specialization of hap.

ap_SOP :: POP (f -.-> g) xss -> SOP f xss -> SOP g xss Source #

Specialization of hap.

Lifting / mapping

liftA_NS :: SListI xs => (forall a. f a -> g a) -> NS f xs -> NS g xs Source #

Specialization of hliftA.

liftA_SOP :: All SListI xss => (forall a. f a -> g a) -> SOP f xss -> SOP g xss Source #

Specialization of hliftA.

liftA2_NS :: SListI xs => (forall a. f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs Source #

Specialization of hliftA2.

liftA2_SOP :: All SListI xss => (forall a. f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss Source #

Specialization of hliftA2.

cliftA_NS :: All c xs => proxy c -> (forall a. c a => f a -> g a) -> NS f xs -> NS g xs Source #

Specialization of hcliftA.

cliftA_SOP :: All2 c xss => proxy c -> (forall a. c a => f a -> g a) -> SOP f xss -> SOP g xss Source #

Specialization of hcliftA.

cliftA2_NS :: All c xs => proxy c -> (forall a. c a => f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs Source #

Specialization of hcliftA2.

cliftA2_SOP :: All2 c xss => proxy c -> (forall a. c a => f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss Source #

Specialization of hcliftA2.

map_NS :: SListI xs => (forall a. f a -> g a) -> NS f xs -> NS g xs Source #

Specialization of hmap, which is equivalent to hliftA.

map_SOP :: All SListI xss => (forall a. f a -> g a) -> SOP f xss -> SOP g xss Source #

Specialization of hmap, which is equivalent to hliftA.

cmap_NS :: All c xs => proxy c -> (forall a. c a => f a -> g a) -> NS f xs -> NS g xs Source #

Specialization of hcmap, which is equivalent to hcliftA.

cmap_SOP :: All2 c xss => proxy c -> (forall a. c a => f a -> g a) -> SOP f xss -> SOP g xss Source #

Specialization of hcmap, which is equivalent to hcliftA.

Dealing with All c

cliftA2'_NS :: All2 c xss => proxy c -> (forall xs. All c xs => f xs -> g xs -> h xs) -> NP f xss -> NS g xss -> NS h xss Source #

Deprecated: Use cliftA2_NS instead.

Specialization of hcliftA2'.

Comparison

compare_NS Source #

Arguments

:: r

what to do if first is smaller

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

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: 0.3.2.0

ccompare_NS Source #

Arguments

:: All c xs 
=> proxy c 
-> r

what to do if first is smaller

-> (forall x. 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: 0.3.2.0

compare_SOP Source #

Arguments

:: r

what to do if first is smaller

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

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: 0.3.2.0

ccompare_SOP Source #

Arguments

:: All2 c xss 
=> proxy c 
-> r

what to do if first is smaller

-> (forall xs. 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: 0.3.2.0

Collapsing

collapse_NS :: NS (K a) xs -> a Source #

Specialization of hcollapse.

collapse_SOP :: SListI xss => SOP (K a) xss -> [a] Source #

Specialization of hcollapse.

Folding and sequencing

ctraverse__NS :: forall c proxy xs f g. All c xs => proxy c -> (forall a. c a => f a -> g ()) -> NS f xs -> g () Source #

Specialization of hctraverse_.

Note: we don't need Applicative constraint.

Since: 0.3.2.0

ctraverse__SOP :: forall c proxy xss f g. (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> SOP f xss -> g () Source #

Specialization of hctraverse_.

Since: 0.3.2.0

traverse__NS :: forall xs f g. SListI xs => (forall a. f a -> g ()) -> NS f xs -> g () Source #

Specialization of htraverse_.

Note: we don't need Applicative constraint.

Since: 0.3.2.0

traverse__SOP :: forall xss f g. (SListI2 xss, Applicative g) => (forall a. f a -> g ()) -> SOP f xss -> g () Source #

Specialization of htraverse_.

Since: 0.3.2.0

cfoldMap_NS :: forall c proxy f xs m. All c xs => proxy c -> (forall a. c a => f a -> m) -> NS f xs -> m Source #

Specialization of hcfoldMap.

Note: We don't need Monoid instance.

Since: 0.3.2.0

cfoldMap_SOP :: (All2 c xs, Monoid m) => proxy c -> (forall a. c a => f a -> m) -> SOP f xs -> m Source #

Specialization of hcfoldMap.

Since: 0.3.2.0

sequence'_NS :: Applicative f => NS (f :.: g) xs -> f (NS g xs) Source #

Specialization of hsequence'.

sequence'_SOP :: (SListI xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss) Source #

Specialization of hsequence'.

sequence_NS :: (SListI xs, Applicative f) => NS f xs -> f (NS I xs) Source #

Specialization of hsequence.

sequence_SOP :: (All SListI xss, Applicative f) => SOP f xss -> f (SOP I xss) Source #

Specialization of hsequence.

ctraverse'_NS :: forall c proxy xs f f' g. (All c xs, Functor g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source #

Specialization of hctraverse'.

Note: as NS has exactly one element, the Functor constraint is enough.

Since: 0.3.2.0

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

Specialization of hctraverse'.

Since: 0.3.2.0

traverse'_NS :: forall xs f f' g. (SListI xs, Functor g) => (forall a. f a -> g (f' a)) -> NS f xs -> g (NS f' xs) Source #

Specialization of htraverse'.

Note: as NS has exactly one element, the Functor constraint is enough.

Since: 0.3.2.0

traverse'_SOP :: (SListI2 xss, Applicative g) => (forall a. f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss) Source #

Specialization of htraverse'.

Since: 0.3.2.0

ctraverse_NS :: (All c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> NP f xs -> g (NP I xs) Source #

Specialization of hctraverse.

Since: 0.3.2.0

ctraverse_SOP :: (All2 c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> POP f xs -> g (POP I xs) Source #

Specialization of hctraverse.

Since: 0.3.2.0

Catamorphism and anamorphism

cata_NS :: forall r f xs. (forall y ys. f y -> r (y ': ys)) -> (forall y ys. r ys -> r (y ': ys)) -> NS f xs -> r xs Source #

Catamorphism for NS.

Takes arguments determining what to do for Z and what to do for S. The result type is still indexed over the type-level lit.

Since: 0.2.3.0

ccata_NS :: forall c proxy r f xs. All c xs => proxy c -> (forall y ys. c y => f y -> r (y ': ys)) -> (forall y ys. c y => r ys -> r (y ': ys)) -> NS f xs -> r xs Source #

Constrained catamorphism for NS.

Since: 0.2.3.0

ana_NS :: forall s f xs. SListI xs => (forall r. s '[] -> r) -> (forall y ys. s (y ': ys) -> Either (f y) (s ys)) -> s xs -> NS f xs Source #

Anamorphism for NS.

Since: 0.2.3.0

cana_NS :: forall c proxy s f xs. All c xs => proxy c -> (forall r. s '[] -> r) -> (forall y ys. c y => s (y ': ys) -> Either (f y) (s ys)) -> s xs -> NS f xs Source #

Constrained anamorphism for NS.

Since: 0.2.3.0

Expanding sums to products

expand_NS :: forall f xs. SListI xs => (forall x. f x) -> NS f xs -> NP f xs Source #

Specialization of hexpand.

Since: 0.2.5.0

cexpand_NS :: forall c proxy f xs. All c xs => proxy c -> (forall x. c x => f x) -> NS f xs -> NP f xs Source #

Specialization of hcexpand.

Since: 0.2.5.0

expand_SOP :: forall f xss. All SListI xss => (forall x. f x) -> SOP f xss -> POP f xss Source #

Specialization of hexpand.

Since: 0.2.5.0

cexpand_SOP :: forall c proxy f xss. All2 c xss => proxy c -> (forall x. c x => f x) -> SOP f xss -> POP f xss Source #

Specialization of hcexpand.

Since: 0.2.5.0

Transformation of index lists and coercions

trans_NS :: AllZip c xs ys => proxy c -> (forall x y. c x y => f x -> g y) -> NS f xs -> NS g ys Source #

Specialization of htrans.

Since: 0.3.1.0

trans_SOP :: AllZip2 c xss yss => proxy c -> (forall x y. c x y => f x -> g y) -> SOP f xss -> SOP g yss Source #

Specialization of htrans.

Since: 0.3.1.0

coerce_NS :: forall f g xs ys. AllZip (LiftedCoercible f g) xs ys => NS f xs -> NS g ys Source #

Specialization of hcoerce.

Since: 0.3.1.0

coerce_SOP :: forall f g xss yss. AllZip2 (LiftedCoercible f g) xss yss => SOP f xss -> SOP g yss Source #

Specialization of hcoerce.

Since: 0.3.1.0

fromI_NS :: forall f xs ys. AllZip (LiftedCoercible I f) xs ys => NS I xs -> NS f ys Source #

Specialization of hfromI.

Since: 0.3.1.0

fromI_SOP :: forall f xss yss. AllZip2 (LiftedCoercible I f) xss yss => SOP I xss -> SOP f yss Source #

Specialization of hfromI.

Since: 0.3.1.0

toI_NS :: forall f xs ys. AllZip (LiftedCoercible f I) xs ys => NS f xs -> NS I ys Source #

Specialization of htoI.

Since: 0.3.1.0

toI_SOP :: forall f xss yss. AllZip2 (LiftedCoercible f I) xss yss => SOP f xss -> SOP I yss Source #

Specialization of htoI.

Since: 0.3.1.0