Safe Haskell | None |
---|---|
Language | Haskell2010 |
n-ary sums (and sums of products)
- data NS :: (k -> *) -> [k] -> * where
- newtype SOP f xss = SOP (NS (NP f) xss)
- unSOP :: SOP f xss -> NS (NP f) xss
- type Injection f xs = f -.-> K (NS f xs)
- injections :: forall xs f. SingI xs => NP (Injection f xs) xs
- shift :: Injection f xs a -> Injection f (x : xs) a
- apInjs_NP :: SingI xs => NP f xs -> [NS f xs]
- apInjs_POP :: SingI xss => POP f xss -> [SOP f xss]
- ap_NS :: NP (f -.-> g) xs -> NS f xs -> NS g xs
- ap_SOP :: POP (f -.-> g) xs -> SOP f xs -> SOP g xs
- liftA_NS :: SingI xs => (forall a. f a -> g a) -> NS f xs -> NS g xs
- liftA_SOP :: SingI xss => (forall a. f a -> g a) -> SOP f xss -> SOP g xss
- liftA2_NS :: SingI xs => (forall a. f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs
- liftA2_SOP :: SingI xss => (forall a. f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss
- cliftA_NS :: (All c xs, SingI xs) => Proxy c -> (forall a. c a => f a -> g a) -> NS f xs -> NS g xs
- cliftA_SOP :: (All2 c xss, SingI xss) => Proxy c -> (forall a. c a => f a -> g a) -> SOP f xss -> SOP g xss
- cliftA2_NS :: (All c xs, SingI xs) => Proxy c -> (forall a. c a => f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs
- cliftA2_SOP :: (All2 c xss, SingI xss) => Proxy c -> (forall a. c a => f a -> g a -> h a) -> POP f xss -> SOP g xss -> SOP h xss
- cliftA2'_NS :: (All2 c xss, SingI xss) => Proxy c -> (forall xs. (SingI xs, All c xs) => f xs -> g xs -> h xs) -> NP f xss -> NS g xss -> NS h xss
- collapse_NS :: NS (K a) xs -> a
- collapse_SOP :: SingI xss => SOP (K a) xss -> [a]
- sequence'_NS :: Applicative f => NS (f :.: g) xs -> f (NS g xs)
- sequence'_SOP :: (SingI xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss)
- sequence_NS :: (SingI xs, Applicative f) => NS f xs -> f (NS I xs)
- sequence_SOP :: (SingI xss, Applicative f) => SOP f xss -> f (SOP I xss)
Datatypes
data NS :: (k -> *) -> [k] -> * 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
, 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.K
a
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 (I 1)) :: NS (K Int) '[ Char, Bool ]
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.
An
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.SOP
I
HSequence k [[k]] (SOP k) | |
HCollapse k [[k]] (SOP k) | |
HAp k [[k]] (SOP k) | |
All * Eq (Map * [k] (NP k f) xss) => Eq (SOP k f xss) | |
(All * Eq (Map * [k] (NP k f) xss), All * Ord (Map * [k] (NP k f) xss)) => Ord (SOP k f xss) | |
All * Show (Map * [k] (NP k f) xss) => Show (SOP k f xss) | |
type CollapseTo k [[k]] (SOP k) = [] | |
type Prod k [[k]] (SOP k) = POP k |
Constructing sums
type Injection f xs = 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. SingI 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
Shift an injection.
Given an injection, return an injection into a sum that is one component larger.
apInjs_NP :: SingI 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_POP :: SingI 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))))]
Application
Lifting / mapping
liftA_NS :: SingI xs => (forall a. f a -> g a) -> NS f xs -> NS g xs Source
Specialization of hliftA
.
liftA_SOP :: SingI xss => (forall a. f a -> g a) -> SOP f xss -> SOP g xss Source
Specialization of hliftA
.
liftA2_NS :: SingI xs => (forall a. f a -> g a -> h a) -> NP f xs -> NS g xs -> NS h xs Source
Specialization of hliftA2
.
liftA2_SOP :: SingI 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, SingI 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, SingI 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, SingI 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, SingI 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
.
Dealing with All
c
All
ccliftA2'_NS :: (All2 c xss, SingI xss) => Proxy c -> (forall xs. (SingI xs, All c xs) => f xs -> g xs -> h xs) -> NP f xss -> NS g xss -> NS h xss Source
Specialization of hcliftA2'
.
Collapsing
collapse_NS :: NS (K a) xs -> a Source
Specialization of hcollapse
.
Sequencing
sequence'_NS :: Applicative f => NS (f :.: g) xs -> f (NS g xs) Source
Specialization of hsequence'
.
sequence'_SOP :: (SingI xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss) Source
Specialization of hsequence'
.
sequence_NS :: (SingI xs, Applicative f) => NS f xs -> f (NS I xs) Source
Specialization of hsequence
.
sequence_SOP :: (SingI xss, Applicative f) => SOP f xss -> f (SOP I xss) Source
Specialization of hsequence
.