| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Generics.SOP.Classes
Contents
Description
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 -> *) :: (k -> *) -> l -> *
- class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp h where
- hliftA :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs
- hliftA2 :: (SListIN (Prod h) 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 :: (SListIN (Prod h) 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
- hmap :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs
- hzipWith :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall a. f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hzipWith3 :: (SListIN (Prod h) 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 :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs
- hcliftA2 :: (AllN (Prod h) c 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 :: (AllN (Prod h) c 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
- hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs
- hczipWith :: (AllN (Prod h) c 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
- hczipWith3 :: (AllN (Prod h) c 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 :: (k -> *) -> l -> *) (x :: *) :: *
- class HCollapse h where
- class HAp h => HSequence h where
- hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h) => Applicative f => h f xs -> f (h I xs)
- hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs)
- class HIndex h where
- type family UnProd (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> *
- class UnProd (Prod h) ~ h => HApInjs h where
- class HExpand h where
Generalized applicative functor structure
Generalized pure
Methods
hpure :: SListIN h xs => (forall a. f a) -> h f xs Source #
Corresponds to pure directly.
Instances:
hpure,pure_NP::SListIxs => (forall a. f a) ->NPf xshpure,pure_POP::SListI2xss => (forall a. f a) ->POPf xss
hcpure :: AllN 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 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 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 AllMap h c NoConstraint xshpure
 separately and directly, and make it a member of the class.
Instances:
hcpure,cpure_NP:: (Allc xs ) => proxy c -> (forall a. c a => f a) ->NPf xshcpure,cpure_POP:: (All2c xss) => proxy c -> (forall a. c a => f a) ->POPf xss
Generalized <*>
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 -> *) :: (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 <*>.
Minimal complete definition
Methods
hap :: Prod h (f -.-> g) xs -> h f xs -> h g xs Source #
Corresponds to <*>.
For products (NP) as well as products of products
 (POP), 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 ->NPf xs ->NPg xshap,ap_NS::NP(f -.-> g) xs ->NSf xs ->NSg xshap,ap_POP::POP(f -.-> g) xss ->POPf xss ->POPg xsshap,ap_SOP::POP(f -.-> g) xss ->SOPf xss ->SOPg xss
Derived functions
hliftA :: (SListIN (Prod h) 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:
hliftAf xs =hpure(fnf) `hap` xs
Instances:
hliftA,liftA_NP::SListIxs => (forall a. f a -> f' a) ->NPf xs ->NPf' xshliftA,liftA_NS::SListIxs => (forall a. f a -> f' a) ->NSf xs ->NSf' xshliftA,liftA_POP::SListI2xss => (forall a. f a -> f' a) ->POPf xss ->POPf' xsshliftA,liftA_SOP::SListI2xss => (forall a. f a -> f' a) ->SOPf xss ->SOPf' xss
hliftA2 :: (SListIN (Prod h) 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:
hliftA2f xs ys =hpure(fn_2f) `hap` xs `hap` ys
Instances:
hliftA2,liftA2_NP::SListIxs => (forall a. f a -> f' a -> f'' a) ->NPf xs ->NPf' xs ->NPf'' xshliftA2,liftA2_NS::SListIxs => (forall a. f a -> f' a -> f'' a) ->NPf xs ->NSf' xs ->NSf'' xshliftA2,liftA2_POP::SListI2xss => (forall a. f a -> f' a -> f'' a) ->POPf xss ->POPf' xss ->POPf'' xsshliftA2,liftA2_SOP::SListI2xss => (forall a. f a -> f' a -> f'' a) ->POPf xss ->SOPf' xss ->SOPf'' xss
hliftA3 :: (SListIN (Prod h) 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:
hliftA3f xs ys zs =hpure(fn_3f) `hap` xs `hap` ys `hap` zs
Instances:
hliftA3,liftA3_NP::SListIxs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NPf xs ->NPf' xs ->NPf'' xs ->NPf''' xshliftA3,liftA3_NS::SListIxs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NPf xs ->NPf' xs ->NSf'' xs ->NSf''' xshliftA3,liftA3_POP::SListI2xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POPf xss ->POPf' xss ->POPf'' xss ->POPf''' xshliftA3,liftA3_SOP::SListI2xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POPf xss ->POPf' xss ->SOPf'' xss ->SOPf''' xs
hmap :: (SListIN (Prod h) xs, HAp h) => (forall a. f a -> f' a) -> h f xs -> h f' xs Source #
Another name for hliftA.
Since: 0.2
hzipWith :: (SListIN (Prod h) 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 #
Another name for hliftA2.
Since: 0.2
hzipWith3 :: (SListIN (Prod h) 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 #
Another name for hliftA3.
Since: 0.2
hcliftA :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs Source #
hcliftA2 :: (AllN (Prod h) c 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 :: (AllN (Prod h) c 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 #
hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall a. c a => f a -> f' a) -> h f xs -> h f' xs Source #
Another name for hcliftA.
Since: 0.2
hczipWith :: (AllN (Prod h) c 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 #
Another name for hcliftA2.
Since: 0.2
hczipWith3 :: (AllN (Prod h) c 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 #
Another name for hcliftA3.
Since: 0.2
Collapsing homogeneous structures
type family CollapseTo (h :: (k -> *) -> l -> *) (x :: *) :: * Source #
Maps products to lists, and sums to identities.
Instances
| type CollapseTo [[k]] k (POP k) a Source # | |
| type CollapseTo [[k]] k (SOP k) a Source # | |
| type CollapseTo [k] k (NP k) a Source # | |
| type CollapseTo [k] k (NS k) a Source # | |
class HCollapse h where Source #
A class for collapsing a heterogeneous structure into a homogeneous one.
Minimal complete definition
Methods
hcollapse :: SListIN h 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 NS (K a)a, and an NP (K a)as.
Instances:
hcollapse,collapse_NP::NP(Ka) xs -> [a]hcollapse,collapse_NS::NS(Ka) xs -> ahcollapse,collapse_POP::POP(Ka) xss -> [[a]]hcollapse,collapse_SOP::SOP(Ka) xss -> [a]
Sequencing effects
class HAp h => HSequence h where Source #
A generalization of sequenceA.
Minimal complete definition
Methods
hsequence' :: (SListIN h 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:: (SListIxs ,Applicativef) =>NP(f:.:g) xs -> f (NPg xs )hsequence',sequence'_NS:: (SListIxs ,Applicativef) =>NS(f:.:g) xs -> f (NSg xs )hsequence',sequence'_POP:: (SListI2xss,Applicativef) =>POP(f:.:g) xss -> f (POPg xss)hsequence',sequence'_SOP:: (SListI2xss,Applicativef) =>SOP(f:.:g) xss -> f (SOPg xss)
Derived functions
hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h) => Applicative f => h f xs -> f (h I xs) Source #
Special case of hsequence' where g = .I
hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a)) xs -> f (h (K a) xs) Source #
Special case of hsequence' where g = .K a
Indexing into sums
A class for determining which choice in a sum-like structure a value represents.
Minimal complete definition
Methods
hindex :: h f xs -> Int Source #
If h is a sum-like structure representing a choice
 between n different options, and x is a value of
 type h f xs, then hindex x0 and n - 1 representing the index of the choice
 made by x.
Instances:
hindex,index_NS::NSf xs -> Inthindex,index_SOP::SOPf xs -> Int
Examples:
>>>hindex (S (S (Z (I False))))2>>>hindex (Z (K ()))0>>>hindex (SOP (S (Z (I True :* I 'x' :* Nil))))1
Since: 0.2.4.0
Applying all injections
type family UnProd (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> * Source #
Maps a structure containing products to the corresponding sum structure.
Since: 0.2.4.0
class UnProd (Prod h) ~ h => HApInjs h where Source #
A class for applying all injections corresponding to a sum-like structure to a table containing suitable arguments.
Minimal complete definition
Methods
hapInjs :: SListIN h xs => Prod h f xs -> [h f xs] Source #
For a given table (product-like structure), produce a list where each element corresponds to the application of an injection function into the corresponding sum-like structure.
Instances:
hapInjs,apInjs_NP::SListIxs =>NPf xs -> [NSf xs ]hapInjs,apInjs_SOP::SListI2xss =>POPf xs -> [SOPf xss]
Examples:
>>>hapInjs (I 'x' :* I True :* I 2 :* Nil)[Z (I 'x'), S (Z (I True)), S (S (Z (I 2)))]
>>>hapInjs (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil)[SOP (Z (I 'x' :* Nil)), SOP (S (Z (I True :* (I 2 :* Nil))))]
Since: 0.2.4.0
Expanding sums to products
class HExpand h where Source #
A class for expanding sum structures into corresponding product structures, filling in the slots not targeted by the sum with default values.
Since: 0.2.5.0
Methods
hexpand :: SListIN (Prod h) xs => (forall x. f x) -> h f xs -> Prod h f xs Source #
Expand a given sum structure into a corresponding product structure by placing the value contained in the sum into the corresponding position in the product, and using the given default value for all other positions.
Instances:
hexpand,expand_NS::SListIxs => (forall x . f x) ->NSf xs ->NPf xshexpand,expand_SOP::SListI2xss => (forall x . f x) ->SOPf xss ->POPf xss
Examples:
>>>hexpand Nothing (S (Z (Just 3))) :: NP Maybe '[Char, Int, Bool]Nothing :* Just 3 :* Nothing :* Nil>>>hexpand [] (SOP (S (Z ([1,2] :* "xyz" :* Nil)))) :: POP [] '[ '[Bool], '[Int, Char] ]POP (([] :* Nil) :* ([1,2] :* "xyz" :* Nil) :* Nil)
Since: 0.2.5.0
hcexpand :: AllN (Prod h) c xs => proxy c -> (forall x. c x => f x) -> h f xs -> Prod h f xs Source #
Variant of hexpand that allows passing a constrained default.
Instances:
hcexpand,cexpand_NS::Allc xs => proxy c -> (forall x . c x => f x) ->NSf xs ->NPf xshcexpand,cexpand_SOP::All2c xss => proxy c -> (forall x . c x => f x) ->SOPf xss ->POPf xss
Examples:
>>>hcexpand (Proxy :: Proxy Bounded) (I minBound) (S (Z (I 20))) :: NP I '[Bool, Int, Ordering]I False :* I 20 :* I LT :* Nil>>>hcexpand (Proxy :: Proxy Num) (I 0) (SOP (S (Z (I 1 :* I 2 :* Nil)))) :: POP I '[ '[Double], '[Int, Int] ]POP ((I 0.0 :* Nil) :* (I 1 :* I 2 :* Nil) :* Nil)
Since: 0.2.5.0