generics-sop-0.2.1.0: Generic Programming using True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Classes

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 product
  NS  :: (k -> *) -> ( [k]  -> *)   -- n-ary sum
  POP :: (k -> *) -> ([[k]] -> *)   -- product of products
  SOP :: (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.

Synopsis

Documentation

class HPure h where Source

A generalization of pure or return to higher kinds.

Methods

hpure :: SListIN h xs => (forall a. f a) -> h f xs Source

Corresponds to pure directly.

Instances:

hpure, pure_NP  :: SListI  xs  => (forall a. f a) -> NP  f xs
hpure, pure_POP :: SListI2 xss => (forall a. f a) -> POP f 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 s where s :: 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 states.

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 xs is always satisfied. Therefore, we typically define hpure separately and directly, and make it a member of the class.

Instances:

hcpure, cpure_NP  :: (All  c xs ) => proxy c -> (forall a. c a => f a) -> NP  f xs
hcpure, cpure_POP :: (All2 c xss) => proxy c -> (forall a. c a => f a) -> POP f xss

Instances

HPure k [[k]] (POP k) Source 
HPure k [k] (NP k) Source 

newtype (f -.-> g) a infixr 1 Source

Lifted functions.

Constructors

Fn 

Fields

apFn :: f a -> g a
 

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.

Instances

type Prod k [[k]] (POP k) = POP k Source 
type Prod k [k] (NP k) = NP k Source 
type Prod k [[k]] (SOP k) = POP k Source 
type Prod k [k] (NS k) = NP k Source 

class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp h where Source

A generalization of <*>.

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  -> NP  f xs  -> NP  g xs
hap, ap_NS  :: NP  (f -.-> g) xs  -> NS  f xs  -> NS  g xs
hap, ap_POP :: POP (f -.-> g) xss -> POP f xss -> POP g xss
hap, ap_SOP :: POP (f -.-> g) xss -> SOP f xss -> SOP g xss

Instances

HAp k [[k]] (POP k) Source 
HAp k [k] (NP k) Source 
HAp k [[k]] (SOP k) Source 
HAp k [k] (NS k) Source 

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:

hliftA f xs = hpure (fn f) ` hap ` xs

Instances:

hliftA, liftA_NP  :: SListI  xs  => (forall a. f a -> f' a) -> NP  f xs  -> NP  f' xs
hliftA, liftA_NS  :: SListI  xs  => (forall a. f a -> f' a) -> NS  f xs  -> NS  f' xs
hliftA, liftA_POP :: SListI2 xss => (forall a. f a -> f' a) -> POP f xss -> POP f' xss
hliftA, liftA_SOP :: SListI2 xss => (forall a. f a -> f' a) -> SOP f xss -> SOP f' 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:

hliftA2 f xs ys = hpure (fn_2 f) ` hap ` xs ` hap ` ys

Instances:

hliftA2, liftA2_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs
hliftA2, liftA2_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NS  f' xs  -> NS  f'' xs
hliftA2, liftA2_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> POP f' xss -> POP f'' xss
hliftA2, liftA2_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> SOP f' xss -> SOP f'' 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:

hliftA3 f xs ys zs = hpure (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

Instances:

hliftA3, liftA3_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs  -> NP  f''' xs
hliftA3, liftA3_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NS  f'' xs  -> NS  f''' xs
hliftA3, liftA3_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> POP f'' xss -> POP f''' xs
hliftA3, liftA3_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> SOP f'' xss -> SOP f''' 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.

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.

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.

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

Variant of hliftA that takes a constrained function.

Specification:

hcliftA p f xs = hcpure p (fn f) ` hap ` 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 Source

Variant of hcliftA2 that takes a constrained function.

Specification:

hcliftA2 p f xs ys = hcpure p (fn_2 f) ` hap ` xs ` hap ` ys

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

Variant of hcliftA3 that takes a constrained function.

Specification:

hcliftA3 p f xs ys zs = hcpure p (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

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.

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.

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.

type family CollapseTo h x :: * Source

Maps products to lists, and sums to identities.

Instances

type CollapseTo k [[k]] (POP k) a = [[a]] Source 
type CollapseTo k [k] (NP k) a = [a] Source 
type CollapseTo k [[k]] (SOP k) a = [a] Source 
type CollapseTo k [k] (NS k) a = a Source 

class HCollapse h where Source

A class for collapsing a heterogeneous structure into a homogeneous one.

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) contains a single a, and an NP (K a) contains a list of as.

Instances:

hcollapse, collapse_NP  :: NP  (K a) xs  ->  [a]
hcollapse, collapse_NS  :: NS  (K a) xs  ->   a
hcollapse, collapse_POP :: POP (K a) xss -> [[a]]
hcollapse, collapse_SOP :: SOP (K a) xss ->  [a]

Instances

HCollapse k [[k]] (POP k) Source 
HCollapse k [k] (NP k) Source 
HCollapse k [[k]] (SOP k) Source 
HCollapse k [k] (NS k) Source 

class HAp h => HSequence h where Source

A generalization of sequenceA.

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  :: (SListI  xs , Applicative f) => NP  (f :.: g) xs  -> f (NP  g xs )
hsequence', sequence'_NS  :: (SListI  xs , Applicative f) => NS  (f :.: g) xs  -> f (NS  g xs )
hsequence', sequence'_POP :: (SListI2 xss, Applicative f) => POP (f :.: g) xss -> f (POP g xss)
hsequence', sequence'_SOP :: (SListI2 xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g xss)

Instances

HSequence k [[k]] (POP k) Source 
HSequence k [k] (NP k) Source 
HSequence k [[k]] (SOP k) Source 
HSequence k [k] (NS k) Source 

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.