Safe Haskell | None |
---|---|
Language | Haskell2010 |
Classes for generalized combinators on SOP types.
In the SOP approach to generic programming, we're predominantly concerned with four structured datatypes:
NP
:: (k -> *) -> ( [k] -> *) -- n-ary productNS
:: (k -> *) -> ( [k] -> *) -- n-ary sumPOP
:: (k -> *) -> ([[k]] -> *) -- product of productsSOP
:: (k -> *) -> ([[k]] -> *) -- sum of products
All of these have a kind that fits the following pattern:
(k -> *) -> (l -> *)
These four types support similar interfaces. In order to allow reusing the same combinator names for all of these types, we define various classes in this module that allow the necessary generalization.
The classes typically lift concepts that exist for kinds *
or
* -> *
to datatypes of kind (k -> *) -> (l -> *)
. This module
also derives a number of derived combinators.
The actual instances are defined in Generics.SOP.NP and Generics.SOP.NS.
- class HPure h where
- newtype (f -.-> g) a = Fn {
- apFn :: f a -> g a
- fn :: (f a -> f' a) -> (f -.-> f') a
- fn_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a
- fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a
- fn_4 :: (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a
- type family Prod h :: (k -> *) -> l -> *
- class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp h where
- hliftA :: (SingI xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs
- hliftA2 :: (SingI xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hliftA3 :: (SingI xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hcliftA :: (AllMap (Prod h) c xs, SingI xs, HAp h) => Proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs
- hcliftA2 :: (AllMap (Prod h) c xs, SingI xs, HAp h, HAp (Prod h)) => Proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hcliftA3 :: (AllMap (Prod h) c xs, SingI xs, HAp h, HAp (Prod h)) => Proxy c -> (forall a. c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- type family CollapseTo h :: * -> *
- class HCollapse h where
- hcollapse :: SingI xs => h (K a) xs -> CollapseTo h a
- class HAp h => HSequence h where
- hsequence' :: (SingI xs, Applicative f) => h (f :.: g) xs -> f (h g xs)
- hsequence :: (SingI xs, HSequence h) => Applicative f => h f xs -> f (h I xs)
- hsequenceK :: (SingI xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs)
Documentation
hpure :: SingI xs => (forall a. f a) -> h f xs Source
Corresponds to pure
directly.
Instances:
hpure
,pure_NP
::SingI
xs => (forall a. f a) ->NP
f xshpure
,pure_POP
::SingI
xss => (forall a. f a) ->POP
f xss
hcpure :: (SingI xs, AllMap h c xs) => Proxy c -> (forall a. c a => f a) -> h f xs Source
A variant of hpure
that allows passing in a constrained
argument.
Calling
where hcpure
f ss :: 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
states.AllMap
h c xs
Morally, hpure
is a special case of hcpure
where the
constraint is empty. However, it is in the nature of how AllMap
is defined as well as current GHC limitations that it is tricky
to prove to GHC in general that
is
always satisfied. Therefore, we typically define AllMap
h c NoConstraint xshpure
separately and directly, and make it a member of the class.
Instances:
hcpure
,cpure_NP
:: (SingI
xs,All
c xs ) =>Proxy
c -> (forall a. c a => f a) ->NP
f xshcpure
,cpure_POP
:: (SingI
xss,All2
c xss) =>Proxy
c -> (forall a. c a => f a) ->POP
f xss
fn :: (f a -> f' a) -> (f -.-> f') a Source
Construct a lifted function.
Same as Fn
. Only available for uniformity with the
higher-arity versions.
fn_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a Source
Construct a binary lifted function.
fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a Source
Construct a ternary lifted function.
fn_4 :: (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a Source
Construct a quarternary lifted function.
type family Prod h :: (k -> *) -> l -> * Source
Maps a structure containing sums to the corresponding product structure.
class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp h where Source
A generalization of <*>
.
hap :: Prod h (f -.-> g) xs -> h f xs -> h g xs Source
Corresponds to <*>
.
For products as well as products or products, 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 xshap
,ap_NS
::NP
(f -.-> g) xs ->NS
f xs ->NS
g xshap
,ap_POP
::POP
(f -.-> g) xss ->POP
f xss ->POP
g xsshap
,ap_SOP
::POP
(f -.-> g) xss ->SOP
f xss ->SOP
g xss
hliftA :: (SingI xs, HAp h) => (forall a. 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
::SingI
xs => (forall a. f a -> f' a) ->NP
f xs ->NP
f' xshliftA
,liftA_NS
::SingI
xs => (forall a. f a -> f' a) ->NS
f xs ->NS
f' xshliftA
,liftA_POP
::SingI
xss => (forall a. f a -> f' a) ->POP
f xss ->POP
f' xsshliftA
,liftA_SOP
::SingI
xss => (forall a. f a -> f' a) ->SOP
f xss ->SOP
f' xss
hliftA2 :: (SingI xs, HAp h, HAp (Prod h)) => (forall a. 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
::SingI
xs => (forall a. f a -> f' a -> f'' a) ->NP
f xs ->NP
f' xs ->NP
f'' xshliftA2
,liftA2_NS
::SingI
xs => (forall a. f a -> f' a -> f'' a) ->NP
f xs ->NS
f' xs ->NS
f'' xshliftA2
,liftA2_POP
::SingI
xss => (forall a. f a -> f' a -> f'' a) ->POP
f xss ->POP
f' xss ->POP
f'' xsshliftA2
,liftA2_SOP
::SingI
xss => (forall a. f a -> f' a -> f'' a) ->POP
f xss ->SOP
f' xss ->SOP
f'' xss
hliftA3 :: (SingI xs, HAp h, HAp (Prod h)) => (forall a. 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
::SingI
xs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NP
f xs ->NP
f' xs ->NP
f'' xs ->NP
f''' xshliftA3
,liftA3_NS
::SingI
xs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NP
f xs ->NP
f' xs ->NS
f'' xs ->NS
f''' xshliftA3
,liftA3_POP
::SingI
xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POP
f xss ->POP
f' xss ->POP
f'' xss ->POP
f''' xshliftA3
,liftA3_SOP
::SingI
xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POP
f xss ->POP
f' xss ->SOP
f'' xss ->SOP
f''' xs
hcliftA :: (AllMap (Prod h) c xs, SingI xs, HAp h) => Proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs Source
hcliftA2 :: (AllMap (Prod h) c xs, SingI xs, HAp h, HAp (Prod h)) => Proxy c -> (forall a. c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs Source
hcliftA3 :: (AllMap (Prod h) c xs, SingI xs, HAp h, HAp (Prod h)) => Proxy c -> (forall a. 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
type family CollapseTo h :: * -> * Source
Maps products to lists, and sums to identities.
type CollapseTo k [[k]] (POP k) = (:.:) * * [] [] | |
type CollapseTo k [k] (NP k) = [] | |
type CollapseTo k [[k]] (SOP k) = [] | |
type CollapseTo k [k] (NS k) = I |
class HCollapse h where Source
A class for collapsing a heterogeneous structure into a homogeneous one.
hcollapse :: SingI xs => h (K a) 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
contains a single NS
(K
a)a
, and an
contains
a list of NP
(K
a)a
s.
Instances:
hcollapse
,collapse_NP
::NP
(K
a) xs -> [a]hcollapse
,collapse_NS
::NS
(K
a) xs -> ahcollapse
,collapse_POP
::POP
(K
a) xss -> [[a]]hcollapse
,collapse_SOP
::SOP
(K
a) xss -> [a]
class HAp h => HSequence h where Source
A generalization of sequenceA
.
hsequence' :: (SingI 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
:: (SingI
xs ,Applicative
f) =>NP
(f:.:
g) xs -> f (NP
g xs )hsequence'
,sequence'_NS
:: (SingI
xs ,Applicative
f) =>NS
(f:.:
g) xs -> f (NS
g xs )hsequence'
,sequence'_POP
:: (SingI
xss,Applicative
f) =>POP
(f:.:
g) xss -> f (POP
g xss)hsequence'
,sequence'_SOP
:: (SingI
xss,Applicative
f) =>SOP
(f:.:
g) xss -> f (SOP
g xss)
hsequence :: (SingI xs, HSequence h) => Applicative f => h f xs -> f (h I xs) Source
Special case of hsequence'
where g =
.I
hsequenceK :: (SingI xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs) Source
Special case of hsequence'
where g =
.K
a