sop-core-0.5.0.1: True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Data.SOP.NP

Contents

Description

n-ary products (and products of products)

Synopsis

Datatypes

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

An n-ary product.

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

The constructor names are chosen to resemble the names of the list constructors.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the product becomes a heterogeneous list, where the type-level list describes the types of its components. For K a, the product becomes a homogeneous list, where the contents of the type-level list are ignored, but its length still specifies the number of elements.

In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.

Examples:

I 'x'    :* I True  :* Nil  ::  NP I       '[ Char, Bool ]
K 0      :* K 1     :* Nil  ::  NP (K Int) '[ Char, Bool ]
Just 'x' :* Nothing :* Nil  ::  NP Maybe   '[ Char, Bool ]

Constructors

Nil :: NP f '[] 
(:*) :: f x -> NP f xs -> NP f (x ': xs) infixr 5 
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) Source # 
Instance details

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

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

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

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

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

Defined in Data.SOP.NP

Methods

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

show :: NP f xs -> String #

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

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

Since: 0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

(<>) :: NP f xs -> NP f xs -> NP f xs #

sconcat :: NonEmpty (NP f xs) -> NP f xs #

stimes :: Integral b => b -> NP f xs -> NP f xs #

(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs) Source #

Since: 0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

mempty :: NP f xs #

mappend :: NP f xs -> NP f xs -> NP f xs #

mconcat :: [NP f xs] -> NP f xs #

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

Since: 0.2.5.0

Instance details

Defined in Data.SOP.NP

Methods

rnf :: NP f xs -> () #

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NS

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

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

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

Defined in Data.SOP.NP

Methods

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

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

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

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

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

max :: POP f xss -> POP f xss -> POP f xss #

min :: POP f xss -> POP f xss -> POP f xss #

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

Defined in Data.SOP.NP

Methods

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

show :: POP f xss -> String #

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

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

Since: 0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

(<>) :: POP f xss -> POP f xss -> POP f xss #

sconcat :: NonEmpty (POP f xss) -> POP f xss #

stimes :: Integral b => b -> POP f xss -> POP f xss #

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

Since: 0.4.0.0

Instance details

Defined in Data.SOP.NP

Methods

mempty :: POP f xss #

mappend :: POP f xss -> POP f xss -> POP f xss #

mconcat :: [POP f xss] -> POP f xss #

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

Since: 0.2.5.0

Instance details

Defined in Data.SOP.NP

Methods

rnf :: POP f xss -> () #

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NS

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

Defined in Data.SOP.NP

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

unPOP :: POP f xss -> NP (NP f) xss Source #

Unwrap a product of products.

Constructing products

pure_NP :: forall f xs. SListI xs => (forall a. f a) -> NP f xs Source #

Specialization of hpure.

The call pure_NP x generates a product that contains x in every element position.

Example:

>>> pure_NP [] :: NP [] '[Char, Bool]
"" :* [] :* Nil
>>> pure_NP (K 0) :: NP (K Int) '[Double, Int, String]
K 0 :* K 0 :* K 0 :* Nil

pure_POP :: All SListI xss => (forall a. f a) -> POP f xss Source #

Specialization of hpure.

The call pure_POP x generates a product of products that contains x in every element position.

cpure_NP :: forall c xs proxy f. All c xs => proxy c -> (forall a. c a => f a) -> NP f xs Source #

Specialization of hcpure.

The call cpure_NP p x generates a product that contains x in every element position.

cpure_POP :: forall c xss proxy f. All2 c xss => proxy c -> (forall a. c a => f a) -> POP f xss Source #

Specialization of hcpure.

The call cpure_NP p x generates a product of products that contains x in every element position.

Construction from a list

fromList :: SListI xs => [a] -> Maybe (NP (K a) 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.

Application

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

Specialization of hap.

Applies a product of (lifted) functions pointwise to a product of suitable arguments.

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

Specialization of hap.

Applies a product of (lifted) functions pointwise to a product of suitable arguments.

Destructing products

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

Obtain the head of an n-ary product.

Since: 0.2.1.0

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

Obtain the tail of an n-ary product.

Since: 0.2.1.0

type Projection (f :: k -> Type) (xs :: [k]) = K (NP f xs) -.-> 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.

projections :: forall xs f. 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.

shiftProjection :: Projection f xs a -> Projection f (x ': xs) a Source #

Lifting / mapping

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

Specialization of hliftA.

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

Specialization of hliftA.

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

Specialization of hliftA2.

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

Specialization of hliftA2.

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

Specialization of hliftA3.

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

Specialization of hliftA3.

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

Specialization of hmap, which is equivalent to hliftA.

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

Specialization of hmap, which is equivalent to hliftA.

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

Specialization of hzipWith, which is equivalent to hliftA2.

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

Specialization of hzipWith, which is equivalent to hliftA2.

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

Specialization of hzipWith3, which is equivalent to hliftA3.

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

Specialization of hzipWith3, which is equivalent to hliftA3.

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

Specialization of hcliftA.

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

Specialization of hcliftA.

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

Specialization of hcliftA2.

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

Specialization of hcliftA2.

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

Specialization of hcliftA3.

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

Specialization of hcliftA3.

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

Specialization of hcmap, which is equivalent to hcliftA.

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

Specialization of hcmap, which is equivalent to hcliftA.

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

Specialization of hczipWith, which is equivalent to hcliftA2.

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

Specialization of hczipWith, which is equivalent to hcliftA2.

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

Specialization of hczipWith3, which is equivalent to hcliftA3.

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

Specialization of hczipWith3, which is equivalent to hcliftA3.

Dealing with All c

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

Deprecated: Use hcliftA or hcmap instead.

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

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

Deprecated: Use hcliftA2 or hczipWith instead.

Like hcliftA', but for binary functions.

hcliftA3' :: (All2 c xss, Prod h ~ NP, HAp h) => proxy c -> (forall xs. 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 #

Deprecated: Use hcliftA3 or hczipWith3 instead.

Like hcliftA', but for ternary functions.

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

Deprecated: Use cliftA2_NP instead.

Specialization of hcliftA2'.

Collapsing

collapse_NP :: NP (K a) xs -> [a] Source #

Specialization of hcollapse.

Example:

>>> collapse_NP (K 1 :* K 2 :* K 3 :* Nil)
[1,2,3]

collapse_POP :: SListI xss => POP (K a) xss -> [[a]] Source #

Specialization of hcollapse.

Example:

>>> collapse_POP (POP ((K 'a' :* Nil) :* (K 'b' :* K 'c' :* Nil) :* Nil) :: POP (K Char) '[ '[(a :: Type)], '[b, c] ])
["a","bc"]

(The type signature is only necessary in this case to fix the kind of the type variables.)

Folding and sequencing

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

Specialization of hctraverse_.

Since: 0.3.2.0

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

Specialization of hctraverse_.

Since: 0.3.2.0

traverse__NP :: forall xs f g. (SListI xs, Applicative g) => (forall a. f a -> g ()) -> NP f xs -> g () Source #

Specialization of htraverse_.

Since: 0.3.2.0

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

Specialization of htraverse_.

Since: 0.3.2.0

cfoldMap_NP :: (All c xs, Monoid m) => proxy c -> (forall a. c a => f a -> m) -> NP f xs -> m Source #

Specialization of hcfoldMap.

Since: 0.3.2.0

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

Specialization of hcfoldMap.

Since: 0.3.2.0

sequence'_NP :: Applicative f => NP (f :.: g) xs -> f (NP g xs) Source #

Specialization of hsequence'.

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

Specialization of hsequence'.

sequence_NP :: (SListI xs, Applicative f) => NP f xs -> f (NP I xs) Source #

Specialization of hsequence.

Example:

>>> sequence_NP (Just 1 :* Just 2 :* Nil)
Just (I 1 :* I 2 :* Nil)

sequence_POP :: (All SListI xss, Applicative f) => POP f xss -> f (POP I xss) Source #

Specialization of hsequence.

Example:

>>> sequence_POP (POP ((Just 1 :* Nil) :* (Just 2 :* Just 3 :* Nil) :* Nil))
Just (POP ((I 1 :* Nil) :* (I 2 :* I 3 :* Nil) :* Nil))

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

Specialization of hctraverse'.

Since: 0.3.2.0

ctraverse'_POP :: (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss) Source #

Specialization of hctraverse'.

Since: 0.3.2.0

traverse'_NP :: forall xs f f' g. (SListI xs, Applicative g) => (forall a. f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source #

Specialization of htraverse'.

Since: 0.3.2.0

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

Specialization of hctraverse'.

Since: 0.3.2.0

ctraverse_NP :: (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_POP :: (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_NP :: forall r f xs. r '[] -> (forall y ys. f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs Source #

Catamorphism for NP.

This is a suitable generalization of foldr. It takes parameters on what to do for Nil and :*. Since the input list is heterogeneous, the result is also indexed by a type-level list.

Since: 0.2.3.0

ccata_NP :: forall c proxy r f xs. All c xs => proxy c -> r '[] -> (forall y ys. c y => f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs Source #

Constrained catamorphism for NP.

The difference compared to cata_NP is that the function for the cons-case can make use of the fact that the specified constraint holds for all the types in the signature of the product.

Since: 0.2.3.0

ana_NP :: forall s f xs. SListI xs => (forall y ys. s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs Source #

Anamorphism for NP.

In contrast to the anamorphism for normal lists, the generating function does not return an Either, but simply an element and a new seed value.

This is because the decision on whether to generate a Nil or a :* is determined by the types.

Since: 0.2.3.0

cana_NP :: forall c proxy s f xs. All c xs => proxy c -> (forall y ys. c y => s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs Source #

Constrained anamorphism for NP.

Compared to ana_NP, the generating function can make use of the specified constraint here for the elements that it generates.

Since: 0.2.3.0

Transformation of index lists and coercions

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

Specialization of htrans.

Since: 0.3.1.0

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

Specialization of htrans.

Since: 0.3.1.0

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

Specialization of hcoerce.

Since: 0.3.1.0

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

Specialization of hcoerce.

Since: 0.3.1.0

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

Specialization of hfromI.

Since: 0.3.1.0

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

Specialization of hfromI.

Since: 0.3.1.0

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

Specialization of htoI.

Since: 0.3.1.0

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

Specialization of htoI.

Since: 0.3.1.0