Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.SOP.NP
Description
n-ary products (and products of products)
Synopsis
- data NP (a :: k -> Type) (b :: [k]) where
- newtype POP (f :: k -> Type) (xss :: [[k]]) = POP (NP (NP f) xss)
- unPOP :: forall {k} (f :: k -> Type) (xss :: [[k]]). POP f xss -> NP (NP f) xss
- pure_NP :: forall {k} f (xs :: [k]). SListI xs => (forall (a :: k). f a) -> NP f xs
- pure_POP :: forall {k} (xss :: [[k]]) f. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a) -> POP f xss
- cpure_NP :: forall {k} c (xs :: [k]) proxy f. All c xs => proxy c -> (forall (a :: k). c a => f a) -> NP f xs
- cpure_POP :: forall {k} c (xss :: [[k]]) proxy f. All2 c xss => proxy c -> (forall (a :: k). c a => f a) -> POP f xss
- fromList :: forall {k} (xs :: [k]) a. SListI xs => [a] -> Maybe (NP (K a :: k -> Type) xs)
- ap_NP :: forall {k} (f :: k -> Type) (g :: k -> Type) (xs :: [k]). NP (f -.-> g) xs -> NP f xs -> NP g xs
- ap_POP :: forall {k} (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). POP (f -.-> g) xss -> POP f xss -> POP g xss
- hd :: forall {k} f (x :: k) (xs :: [k]). NP f (x ': xs) -> f x
- tl :: forall {k} (f :: k -> Type) (x :: k) (xs :: [k]). NP f (x ': xs) -> NP f xs
- type Projection (f :: k -> Type) (xs :: [k]) = (K (NP f xs) :: k -> Type) -.-> f
- projections :: forall {k} (xs :: [k]) (f :: k -> Type). SListI xs => NP (Projection f xs) xs
- shiftProjection :: forall {a1} (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Projection f xs a2 -> Projection f (x ': xs) a2
- liftA_NP :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NP f xs -> NP g xs
- liftA_POP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> POP f xss -> POP g xss
- liftA2_NP :: forall {k} (xs :: [k]) f g h. SListI xs => (forall (a :: k). f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs
- liftA2_POP :: forall {k} (xss :: [[k]]) f g h. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss
- liftA3_NP :: forall {k} (xs :: [k]) f g h i. SListI xs => (forall (a :: k). f a -> g a -> h a -> i a) -> NP f xs -> NP g xs -> NP h xs -> NP i xs
- liftA3_POP :: forall {k} (xss :: [[k]]) f g h i. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a -> i a) -> POP f xss -> POP g xss -> POP h xss -> POP i xss
- map_NP :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NP f xs -> NP g xs
- map_POP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> POP f xss -> POP g xss
- zipWith_NP :: forall {k} (xs :: [k]) f g h. SListI xs => (forall (a :: k). f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs
- zipWith_POP :: forall {k} (xss :: [[k]]) f g h. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss
- zipWith3_NP :: forall {k} (xs :: [k]) f g h i. SListI xs => (forall (a :: k). f a -> g a -> h a -> i a) -> NP f xs -> NP g xs -> NP h xs -> NP i xs
- zipWith3_POP :: forall {k} (xss :: [[k]]) f g h i. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a -> i a) -> POP f xss -> POP g xss -> POP h xss -> POP i xss
- cliftA_NP :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NP f xs -> NP g xs
- cliftA_POP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> POP f xss -> POP g xss
- cliftA2_NP :: forall {k} c (xs :: [k]) proxy f g h. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs
- cliftA2_POP :: forall {k} c (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss
- cliftA3_NP :: forall {k} c (xs :: [k]) proxy f g h i. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a -> i a) -> NP f xs -> NP g xs -> NP h xs -> NP i xs
- cliftA3_POP :: forall {k} c (xss :: [[k]]) proxy f g h i. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a -> i a) -> POP f xss -> POP g xss -> POP h xss -> POP i xss
- cmap_NP :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NP f xs -> NP g xs
- cmap_POP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> POP f xss -> POP g xss
- czipWith_NP :: forall {k} c (xs :: [k]) proxy f g h. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs
- czipWith_POP :: forall {k} c (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss
- czipWith3_NP :: forall {k} c (xs :: [k]) proxy f g h i. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a -> i a) -> NP f xs -> NP g xs -> NP h xs -> NP i xs
- czipWith3_POP :: forall {k} c (xss :: [[k]]) proxy f g h i. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a -> i a) -> POP f xss -> POP g xss -> POP h xss -> POP i xss
- 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
- 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
- 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
- cliftA2'_NP :: forall {k} (c :: k -> Constraint) (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (xs :: [k]). All c xs => f xs -> g xs -> h xs) -> NP f xss -> NP g xss -> NP h xss
- collapse_NP :: forall {k} a (xs :: [k]). NP (K a :: k -> Type) xs -> [a]
- collapse_POP :: forall {k} (xss :: [[k]]) a. SListI xss => POP (K a :: k -> Type) xss -> [[a]]
- ctraverse__NP :: forall {k} c proxy (xs :: [k]) f g. (All c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NP f xs -> g ()
- ctraverse__POP :: forall {k} c proxy (xss :: [[k]]) f g. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> POP f xss -> g ()
- traverse__NP :: forall {k} (xs :: [k]) f g. (SListI xs, Applicative g) => (forall (a :: k). f a -> g ()) -> NP f xs -> g ()
- traverse__POP :: forall {k} (xss :: [[k]]) f g. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g ()) -> POP f xss -> g ()
- cfoldMap_NP :: forall {k} c (xs :: [k]) m proxy f. (All c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> NP f xs -> m
- cfoldMap_POP :: forall {k} c (xs :: [[k]]) m proxy f. (All2 c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> POP f xs -> m
- sequence'_NP :: forall {k} f (g :: k -> Type) (xs :: [k]). Applicative f => NP (f :.: g) xs -> f (NP g xs)
- sequence'_POP :: forall {k} (xss :: [[k]]) f (g :: k -> Type). (SListI xss, Applicative f) => POP (f :.: g) xss -> f (POP g xss)
- sequence_NP :: forall (xs :: [Type]) f. (SListI xs, Applicative f) => NP f xs -> f (NP I xs)
- sequence_POP :: forall (xss :: [[Type]]) f. (All (SListI :: [Type] -> Constraint) xss, Applicative f) => POP f xss -> f (POP I xss)
- ctraverse'_NP :: forall {k} c proxy (xs :: [k]) f f' g. (All c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs)
- ctraverse'_POP :: forall {k} c (xss :: [[k]]) g proxy f f'. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
- traverse'_NP :: forall {k} (xs :: [k]) f f' g. (SListI xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> NP f xs -> g (NP f' xs)
- traverse'_POP :: forall {k} (xss :: [[k]]) g f f'. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
- ctraverse_NP :: forall c (xs :: [Type]) g proxy f. (All c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> NP f xs -> g (NP I xs)
- ctraverse_POP :: forall c (xs :: [[Type]]) g proxy f. (All2 c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> POP f xs -> g (POP I xs)
- cata_NP :: forall {a} r f (xs :: [a]). r ('[] :: [a]) -> (forall (y :: a) (ys :: [a]). f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs
- ccata_NP :: forall {a} c proxy r f (xs :: [a]). All c xs => proxy c -> r ('[] :: [a]) -> (forall (y :: a) (ys :: [a]). c y => f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs
- ana_NP :: forall {k} s f (xs :: [k]). SListI xs => (forall (y :: k) (ys :: [k]). s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs
- cana_NP :: forall {k} c proxy s f (xs :: [k]). All c xs => proxy c -> (forall (y :: k) (ys :: [k]). c y => s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs
- trans_NP :: forall {k1} {k2} c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZip c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NP f xs -> NP g ys
- trans_POP :: forall {k1} {k2} c (xss :: [[k1]]) (yss :: [[k2]]) proxy f g. AllZip2 c xss yss => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> POP f xss -> POP g yss
- coerce_NP :: forall {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZip (LiftedCoercible f g) xs ys => NP f xs -> NP g ys
- coerce_POP :: forall {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xss :: [[k1]]) (yss :: [[k2]]). AllZip2 (LiftedCoercible f g) xss yss => POP f xss -> POP g yss
- fromI_NP :: forall {k} (f :: k -> Type) (xs :: [Type]) (ys :: [k]). AllZip (LiftedCoercible I f) xs ys => NP I xs -> NP f ys
- fromI_POP :: forall {k} (f :: k -> Type) (xss :: [[Type]]) (yss :: [[k]]). AllZip2 (LiftedCoercible I f) xss yss => POP I xss -> POP f yss
- toI_NP :: forall {k} (f :: k -> Type) (xs :: [k]) (ys :: [Type]). AllZip (LiftedCoercible f I) xs ys => NP f xs -> NP I ys
- toI_POP :: forall {k} (f :: k -> Type) (xss :: [[k]]) (yss :: [[Type]]). AllZip2 (LiftedCoercible f I) xss yss => POP f xss -> POP I yss
Datatypes
data NP (a :: k -> Type) (b :: [k]) 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
, 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.K
a
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 :: forall {k} (a :: k -> Type). NP a ('[] :: [k]) | |
(:*) :: forall {k} (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NP a xs -> NP a (x ': xs) infixr 5 |
Instances
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) Source # | |
Defined in Data.SOP.NP Methods htrans :: forall c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZipN (Prod (NP :: (k1 -> Type) -> [k1] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NP f xs -> NP g ys Source # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZipN (Prod (NP :: (k1 -> Type) -> [k1] -> Type)) (LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source # | |
HAp (NP :: (k -> Type) -> [k] -> Type) Source # | |
HCollapse (NP :: (k -> Type) -> [k] -> Type) Source # | |
HPure (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP | |
HSequence (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP Methods hsequence' :: forall (xs :: [k]) f (g :: k -> Type). (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) Source # hctraverse' :: forall c (xs :: [k]) g proxy f f'. (AllN (NP :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # htraverse' :: forall (xs :: [k]) g f f'. (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source # | |
HTraverse_ (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP Methods hctraverse_ :: forall c (xs :: [k]) g proxy f. (AllN (NP :: (k -> Type) -> [k] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NP f xs -> g () Source # htraverse_ :: forall (xs :: [k]) g f. (SListIN (NP :: (k -> Type) -> [k] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> NP f xs -> g () Source # | |
(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs) Source # | Since: 0.4.0.0 |
All (Compose Semigroup f) xs => Semigroup (NP f xs) Source # | Since: 0.4.0.0 |
All (Compose Show f) xs => Show (NP f xs) Source # | |
All (Compose NFData f) xs => NFData (NP f xs) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NP | |
All (Compose Eq f) xs => Eq (NP f xs) Source # | |
(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) Source # | |
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type Same (NP :: (k1 -> Type) -> [k1] -> Type) Source # | |
type Prod (NP :: (k -> Type) -> [k] -> Type) Source # | |
type UnProd (NP :: (k -> Type) -> [k] -> Type) Source # | |
type SListIN (NP :: (k -> Type) -> [k] -> Type) Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a Source # | |
Defined in Data.SOP.NP | |
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP |
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.
Instances
HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) Source # | |
Defined in Data.SOP.NP Methods htrans :: forall c (xs :: [[k1]]) (ys :: [[k2]]) proxy f g. AllZipN (Prod (POP :: (k1 -> Type) -> [[k1]] -> Type)) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> POP f xs -> POP g ys Source # hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [[k1]]) (ys :: [[k2]]). AllZipN (Prod (POP :: (k1 -> Type) -> [[k1]] -> Type)) (LiftedCoercible f g) xs ys => POP f xs -> POP g ys Source # | |
HAp (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
HCollapse (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
HPure (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP | |
HSequence (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP Methods hsequence' :: forall (xs :: [[k]]) f (g :: k -> Type). (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) Source # hctraverse' :: forall c (xs :: [[k]]) g proxy f f'. (AllN (POP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # htraverse' :: forall (xs :: [[k]]) g f f'. (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) Source # | |
HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP Methods hctraverse_ :: forall c (xs :: [[k]]) g proxy f. (AllN (POP :: (k -> Type) -> [[k]] -> Type) c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> POP f xs -> g () Source # htraverse_ :: forall (xs :: [[k]]) g f. (SListIN (POP :: (k -> Type) -> [[k]] -> Type) xs, Applicative g) => (forall (a :: k). f a -> g ()) -> POP f xs -> g () Source # | |
Monoid (NP (NP f) xss) => Monoid (POP f xss) Source # | Since: 0.4.0.0 |
Semigroup (NP (NP f) xss) => Semigroup (POP f xss) Source # | Since: 0.4.0.0 |
Show (NP (NP f) xss) => Show (POP f xss) Source # | |
NFData (NP (NP f) xss) => NFData (POP f xss) Source # | Since: 0.2.5.0 |
Defined in Data.SOP.NP | |
Eq (NP (NP f) xss) => Eq (POP f xss) Source # | |
Ord (NP (NP f) xss) => Ord (POP f xss) Source # | |
type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) Source # | |
Defined in Data.SOP.NP | |
type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) Source # | |
type Prod (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
type SListIN (POP :: (k -> Type) -> [[k]] -> Type) Source # | |
Defined in Data.SOP.NP | |
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a Source # | |
Defined in Data.SOP.NP | |
type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) Source # | |
Defined in Data.SOP.NP |
unPOP :: forall {k} (f :: k -> Type) (xss :: [[k]]). POP f xss -> NP (NP f) xss Source #
Unwrap a product of products.
Constructing products
pure_POP :: forall {k} (xss :: [[k]]) f. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a) -> POP f xss Source #
cpure_NP :: forall {k} c (xs :: [k]) proxy f. All c xs => proxy c -> (forall (a :: k). c a => f a) -> NP f xs Source #
cpure_POP :: forall {k} c (xss :: [[k]]) proxy f. All2 c xss => proxy c -> (forall (a :: k). c a => f a) -> POP f xss Source #
Construction from a list
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.
Application
ap_NP :: forall {k} (f :: k -> Type) (g :: k -> Type) (xs :: [k]). 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 :: forall {k} (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). 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 :: forall {k} f (x :: k) (xs :: [k]). NP f (x ': xs) -> f x Source #
Obtain the head of an n-ary product.
Since: 0.2.1.0
tl :: forall {k} (f :: k -> Type) (x :: k) (xs :: [k]). 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) :: 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.
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.
shiftProjection :: forall {a1} (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Projection f xs a2 -> Projection f (x ': xs) a2 Source #
Lifting / mapping
liftA_NP :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NP f xs -> NP g xs Source #
Specialization of hliftA
.
liftA_POP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> POP f xss -> POP g xss Source #
Specialization of hliftA
.
liftA2_NP :: forall {k} (xs :: [k]) f g h. SListI xs => (forall (a :: k). f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs Source #
Specialization of hliftA2
.
liftA2_POP :: forall {k} (xss :: [[k]]) f g h. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss Source #
Specialization of hliftA2
.
liftA3_NP :: forall {k} (xs :: [k]) f g h i. SListI xs => (forall (a :: k). 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 :: forall {k} (xss :: [[k]]) f g h i. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). 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 :: forall {k} (xs :: [k]) f g. SListI xs => (forall (a :: k). f a -> g a) -> NP f xs -> NP g xs Source #
map_POP :: forall {k} (xss :: [[k]]) f g. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a) -> POP f xss -> POP g xss Source #
zipWith_NP :: forall {k} (xs :: [k]) f g h. SListI xs => (forall (a :: k). f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs Source #
zipWith_POP :: forall {k} (xss :: [[k]]) f g h. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss Source #
zipWith3_NP :: forall {k} (xs :: [k]) f g h i. SListI xs => (forall (a :: k). f a -> g a -> h a -> i a) -> NP f xs -> NP g xs -> NP h xs -> NP i xs Source #
zipWith3_POP :: forall {k} (xss :: [[k]]) f g h i. All (SListI :: [k] -> Constraint) xss => (forall (a :: k). f a -> g a -> h a -> i a) -> POP f xss -> POP g xss -> POP h xss -> POP i xss Source #
cliftA_NP :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NP f xs -> NP g xs Source #
Specialization of hcliftA
.
cliftA_POP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> POP f xss -> POP g xss Source #
Specialization of hcliftA
.
cliftA2_NP :: forall {k} c (xs :: [k]) proxy f g h. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs Source #
Specialization of hcliftA2
.
cliftA2_POP :: forall {k} c (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss Source #
Specialization of hcliftA2
.
cliftA3_NP :: forall {k} c (xs :: [k]) proxy f g h i. All c xs => proxy c -> (forall (a :: k). 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 :: forall {k} c (xss :: [[k]]) proxy f g h i. All2 c xss => proxy c -> (forall (a :: k). 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 :: forall {k} c (xs :: [k]) proxy f g. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a) -> NP f xs -> NP g xs Source #
cmap_POP :: forall {k} c (xss :: [[k]]) proxy f g. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a) -> POP f xss -> POP g xss Source #
czipWith_NP :: forall {k} c (xs :: [k]) proxy f g h. All c xs => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> NP f xs -> NP g xs -> NP h xs Source #
czipWith_POP :: forall {k} c (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (a :: k). c a => f a -> g a -> h a) -> POP f xss -> POP g xss -> POP h xss Source #
czipWith3_NP :: forall {k} c (xs :: [k]) proxy f g h i. All c xs => proxy c -> (forall (a :: k). 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 :: forall {k} c (xss :: [[k]]) proxy f g h i. All2 c xss => proxy c -> (forall (a :: k). 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
All
chcliftA' :: 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' xsshcliftA'
::All2
c xss => proxy c -> (forall xs.All
c xs => f xs -> f' xs) ->NS
f xss ->NS
f' xss
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 #
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 #
Deprecated: Use hcliftA3
or hczipWith3
instead.
Like hcliftA'
, but for ternary functions.
cliftA2'_NP :: forall {k} (c :: k -> Constraint) (xss :: [[k]]) proxy f g h. All2 c xss => proxy c -> (forall (xs :: [k]). 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_POP :: forall {k} (xss :: [[k]]) a. SListI xss => POP (K a :: k -> Type) 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 {k} c proxy (xs :: [k]) f g. (All c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> NP f xs -> g () Source #
Specialization of hctraverse_
.
Since: 0.3.2.0
ctraverse__POP :: forall {k} c proxy (xss :: [[k]]) f g. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> POP f xss -> g () Source #
Specialization of hctraverse_
.
Since: 0.3.2.0
traverse__NP :: forall {k} (xs :: [k]) f g. (SListI xs, Applicative g) => (forall (a :: k). f a -> g ()) -> NP f xs -> g () Source #
Specialization of htraverse_
.
Since: 0.3.2.0
traverse__POP :: forall {k} (xss :: [[k]]) f g. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g ()) -> POP f xss -> g () Source #
Specialization of htraverse_
.
Since: 0.3.2.0
cfoldMap_NP :: forall {k} c (xs :: [k]) m proxy f. (All c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> NP f xs -> m Source #
Specialization of hcfoldMap
.
Since: 0.3.2.0
cfoldMap_POP :: forall {k} c (xs :: [[k]]) m proxy f. (All2 c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> POP f xs -> m Source #
Specialization of hcfoldMap
.
Since: 0.3.2.0
sequence'_NP :: forall {k} f (g :: k -> Type) (xs :: [k]). Applicative f => NP (f :.: g) xs -> f (NP g xs) Source #
Specialization of hsequence'
.
sequence'_POP :: forall {k} (xss :: [[k]]) f (g :: k -> Type). (SListI xss, Applicative f) => POP (f :.: g) xss -> f (POP g xss) Source #
Specialization of hsequence'
.
sequence_NP :: forall (xs :: [Type]) f. (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 :: forall (xss :: [[Type]]) f. (All (SListI :: [Type] -> Constraint) 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 {k} c proxy (xs :: [k]) f f' g. (All c xs, Applicative g) => proxy c -> (forall (a :: k). 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 :: forall {k} c (xss :: [[k]]) g proxy f f'. (All2 c xss, Applicative g) => proxy c -> (forall (a :: k). 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 {k} (xs :: [k]) f f' g. (SListI xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) Source #
Specialization of htraverse'
.
Since: 0.3.2.0
traverse'_POP :: forall {k} (xss :: [[k]]) g f f'. (SListI2 xss, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> POP f xss -> g (POP f' xss) Source #
Specialization of hctraverse'
.
Since: 0.3.2.0
ctraverse_NP :: forall c (xs :: [Type]) g proxy f. (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 :: forall c (xs :: [[Type]]) g proxy f. (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 {a} r f (xs :: [a]). r ('[] :: [a]) -> (forall (y :: a) (ys :: [a]). f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs Source #
ccata_NP :: forall {a} c proxy r f (xs :: [a]). All c xs => proxy c -> r ('[] :: [a]) -> (forall (y :: a) (ys :: [a]). c y => f y -> r ys -> r (y ': ys)) -> NP f xs -> r xs Source #
ana_NP :: forall {k} s f (xs :: [k]). SListI xs => (forall (y :: k) (ys :: [k]). s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs Source #
cana_NP :: forall {k} c proxy s f (xs :: [k]). All c xs => proxy c -> (forall (y :: k) (ys :: [k]). c y => s (y ': ys) -> (f y, s ys)) -> s xs -> NP f xs Source #
Transformation of index lists and coercions
trans_NP :: forall {k1} {k2} c (xs :: [k1]) (ys :: [k2]) proxy f g. AllZip c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> NP f xs -> NP g ys Source #
Specialization of htrans
.
Since: 0.3.1.0
trans_POP :: forall {k1} {k2} c (xss :: [[k1]]) (yss :: [[k2]]) proxy f g. AllZip2 c xss yss => proxy c -> (forall (x :: k1) (y :: k2). 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 {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xs :: [k1]) (ys :: [k2]). AllZip (LiftedCoercible f g) xs ys => NP f xs -> NP g ys Source #
Specialization of hcoerce
.
Since: 0.3.1.0
coerce_POP :: forall {k1} {k2} (f :: k1 -> Type) (g :: k2 -> Type) (xss :: [[k1]]) (yss :: [[k2]]). AllZip2 (LiftedCoercible f g) xss yss => POP f xss -> POP g yss Source #
Specialization of hcoerce
.
Since: 0.3.1.0
fromI_NP :: forall {k} (f :: k -> Type) (xs :: [Type]) (ys :: [k]). AllZip (LiftedCoercible I f) xs ys => NP I xs -> NP f ys Source #
Specialization of hfromI
.
Since: 0.3.1.0
fromI_POP :: forall {k} (f :: k -> Type) (xss :: [[Type]]) (yss :: [[k]]). AllZip2 (LiftedCoercible I f) xss yss => POP I xss -> POP f yss Source #
Specialization of hfromI
.
Since: 0.3.1.0