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

Safe HaskellNone
LanguageHaskell2010

Generics.SOP

Contents

Description

Main module of generics-sop

In most cases, you will probably want to import just this module, and possibly Generics.SOP.TH if you want to use Template Haskell to generate Generic instances for you.

Generic programming with sums of products

You need this library if you want to define your own generic functions in the sum-of-products SOP style. Generic programming in the SOP style follows the following idea:

  1. A large class of datatypes can be viewed in a uniform, structured way: the choice between constructors is represented using an n-ary sum (called NS), and the arguments of each constructor are represented using an n-ary product (called NP).
  2. The library captures the notion of a datatype being representable in the following way. There is a class Generic, which for a given datatype A, associates the isomorphic SOP representation with the original type under the name Rep A. The class also provides functions from and to that convert between A and Rep A and witness the isomorphism.
  3. Since all Rep types are sums of products, you can define functions over them by performing induction on the structure, of by using predefined combinators that the library provides. Such functions then work for all Rep types.
  4. By combining the conversion functions from and to with the function that works on Rep types, we obtain a function that works on all types that are in the Generic class.
  5. Most types can very easily be made an instance of Generic. For example, if the datatype can be represented using GHC's built-in approach to generic programming and has an instance for the Generic class from module GHC.Generics, then an instance of the SOP Generic can automatically be derived. There is also Template Haskell code in Generics.SOP.TH that allows to auto-generate an instance of Generic for most types.

Example

Instantiating a datatype for use with SOP generics

Let's assume we have the datatypes:

data A   = C Bool | D A Int | E (B ())
data B a = F | G a Char Bool

To create Generic instances for A and B via GHC.Generics, we say

{-# LANGUAGE DeriveGenerics #-}

import qualified GHC.Generics as GHC
import Generics.SOP

data A   = C Bool | D A Int | E (B ())
  deriving (Show, GHC.Generic)
data B a = F | G a Char Bool
  deriving (Show, GHC.Generic)

instance Generic A     -- empty
instance Generic (B a) -- empty

Now we can convert between A and Rep A (and between B and Rep B). For example,

>>> from (D (C True) 3) :: Rep A
> SOP (S (Z (I (C True) :* I 3 :* Nil)))
>>> to it :: A
> D (C True) 3

Note that the transformation is shallow: In D (C True) 3, the inner value C True of type A is not affected by the transformation.

For more details about Rep A, have a look at the Generics.SOP.Universe module.

Defining a generic function

As an example of a generic function, let us define a generic version of rnf from the deepseq package.

The type of rnf is

NFData a => a -> ()

and the idea is that for a term x of type a in the NFData class, rnf x forces complete evaluation of x (i.e., evaluation to normal form), and returns ().

We call the generic version of this function grnf. A direct definition in SOP style, making use of structural recursion on the sums and products, looks as follows:

grnf :: (Generic a, All2 NFData (Code a)) => a -> ()
grnf x = grnfS (from x)

grnfS :: (All2 NFData xss) => SOP I xss -> ()
grnfS (SOP (Z xs))  = grnfP xs
grnfS (SOP (S xss)) = grnfS (SOP xss)

grnfP :: (All NFData xs) => NP I xs -> ()
grnfP Nil         = ()
grnfP (I x :* xs) = x `deepseq` (grnfP xs)

The grnf function performs the conversion between a and Rep a by applying from and then applies grnfS. The type of grnf indicates that a must be in the Generic class so that we can apply from, and that all the components of a (i.e., all the types that occur as constructor arguments) must be in the NFData class (All2).

The function grnfS traverses the outer sum structure of the sum of products (note that Rep a = SOP I (Code a)). It encodes which constructor was used to construct the original argument of type a. Once we've found the constructor in question (Z), we traverse the arguments of that constructor using grnfP.

The function grnfP traverses the product structure of the constructor arguments. Each argument is evaluated using the deepseq function from the NFData class. This requires that all components of the product must be in the NFData class (All) and triggers the corresponding constraints on the other functions. Once the end of the product is reached (Nil), we return ().

Defining a generic function using combinators

In many cases, generic functions can be written in a much more concise way by avoiding the explicit structural recursion and resorting to the powerful combinators provided by this library instead.

For example, the grnf function can also be defined as a one-liner as follows:

grnf :: (Generic a, All2 NFData (Code a)) => a -> ()
grnf = rnf . hcollapse . hcliftA (Proxy :: Proxy NFData) (\ (I x) -> K (rnf x)) . from

The following interaction should provide an idea of the individual transformation steps:

>>> let x = G 2.5 'A' False :: B Double
>>> from x
> SOP (S (Z (I 2.5 :* I 'A' :* I False :* Nil)))
>>> hcliftA (Proxy :: Proxy NFData) (\ (I x) -> K (rnf x)) it
> SOP (S (Z (K () :* K () :* K () :* Nil)))
>>> hcollapse it
> [(),(),()]
>>> rnf it
> ()

The from call converts into the structural representation. Via hcliftA, we apply rnf to all the components. The result is a sum of products of the same shape, but the components are no longer heterogeneous (I), but homogeneous (K ()). A homogeneous structure can be collapsed (hcollapse) into a normal Haskell list. Finally, rnf actually forces evaluation of this list (and thereby actually drives the evaluation of all the previous steps) and produces the final result.

Using a generic function

We can directly invoke grnf on any type that is an instance of class Generic.

>>> grnf (G 2.5 'A' False)
> ()
>>> grnf (G 2.5 undefined False)
> *** Exception: Prelude.undefined

Note that the type of grnf requires that all components of the type are in the NFData class. For a recursive datatype such as B, this means that we have to make A (and in this case, also B) an instance of NFData in order to be able to use the grnf function. But we can use grnf to supply the instance definitions:

instance NFData A where rnf = grnf
instance NFData a => NFData (B a) where rnf = grnf

More examples

The best way to learn about how to define generic functions in the SOP style is to look at a few simple examples. Examples are provided by the following packages:

The generic functions in these packages use a wide variety of the combinators that are offered by the library.

Paper

A detailed description of the ideas behind this library is provided by the paper:

Synopsis

Codes and interpretations

class SingI (Code a) => Generic a where Source

The class of representable datatypes.

The SOP approach to generic programming is based on viewing datatypes as a representation (Rep) built from the sum of products of its components. The components of are datatype are specified using the Code type family.

The isomorphism between the original Haskell datatype and its representation is witnessed by the methods of this class, from and to. So for instances of this class, the following laws should (in general) hold:

to . from === id :: a -> a
from . to === id :: Rep a -> Rep a

You typically don't define instances of this class by hand, but rather derive the class instance automatically.

Option 1: Derive via the built-in GHC-generics. For this, you need to use the DeriveGeneric extension to first derive an instance of the Generic class from module GHC.Generics. With this, you can then give an empty instance for Generic, and the default definitions will just work. The pattern looks as follows:

import qualified GHC.Generics as GHC
import Generics.SOP

...

data T = ... deriving (GHC.Generic, ...)

instance Generic T -- empty
instance HasDatatypeInfo T -- empty, if you want/need metadata

Option 2: Derive via Template Haskell. For this, you need to enable the TemplateHaskell extension. You can then use deriveGeneric from module Generics.SOP.TH to have the instance generated for you. The pattern looks as follows:

import Generics.SOP
import Generics.SOP.TH

...

data T = ...

deriveGeneric ''T -- derives HasDatatypeInfo as well

Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.

Non-standard instances: It is possible to give Generic instances manually that deviate from the standard scheme, as long as at least

to . from === id :: a -> a

still holds.

Minimal complete definition

Nothing

Associated Types

type Code a :: [[*]] Source

The code of a datatype.

This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).

Example: The datatype

data Tree = Leaf Int | Node Tree Tree

is supposed to have the following code:

type instance Code (Tree a) =
  '[ '[ Int ]
   , '[ Tree, Tree ]
   ]

Methods

from :: a -> Rep a Source

Converts from a value to its structural representation.

to :: Rep a -> a Source

Converts from a structural representation back to the original value.

Instances

Generic Bool 
Generic Ordering 
Generic () 
Generic FormatAdjustment 
Generic FormatSign 
Generic FieldFormat 
Generic FormatParse 
Generic DataRep 
Generic ConstrRep 
Generic Fixity 
Generic Version 
Generic IOMode 
Generic PatternMatchFail 
Generic RecSelError 
Generic RecConError 
Generic RecUpdError 
Generic NoMethodError 
Generic NonTermination 
Generic NestedAtomically 
Generic Errno 
Generic BlockedIndefinitelyOnMVar 
Generic BlockedIndefinitelyOnSTM 
Generic Deadlock 
Generic AssertionFailed 
Generic AsyncException 
Generic ArrayException 
Generic ExitCode 
Generic BufferMode 
Generic Newline 
Generic NewlineMode 
Generic SeekMode 
Generic GeneralCategory 
Generic CChar 
Generic CSChar 
Generic CUChar 
Generic CShort 
Generic CUShort 
Generic CInt 
Generic CUInt 
Generic CLong 
Generic CULong 
Generic CLLong 
Generic CULLong 
Generic CFloat 
Generic CDouble 
Generic CPtrdiff 
Generic CSize 
Generic CWchar 
Generic CSigAtomic 
Generic CClock 
Generic CTime 
Generic CUSeconds 
Generic CSUSeconds 
Generic CIntPtr 
Generic CUIntPtr 
Generic CIntMax 
Generic CUIntMax 
Generic MaskingState 
Generic IOException 
Generic ErrorCall 
Generic ArithException 
Generic All 
Generic Any 
Generic Lexeme 
Generic Number 
Generic [a] 
Generic (ArgOrder a) 
Generic (OptDescr a) 
Generic (ArgDescr a) 
Generic (Fixed a) 
Generic (Complex a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Down a) 
Generic (Maybe a) 
Generic (I a) 
Generic (Either a b) 
Generic (a, b) 
Generic (Proxy * t) 
Typeable (* -> Constraint) Generic 
Generic (a, b, c) 
Generic (K * a b) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic ((:.:) * * f g p) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 
Generic (a, b, c, d, e, f, g, h) 
Generic (a, b, c, d, e, f, g, h, i) 
Generic (a, b, c, d, e, f, g, h, i, j) 
Generic (a, b, c, d, e, f, g, h, i, j, k) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

type Rep a = SOP I (Code a) Source

The (generic) representation of a datatype.

A datatype is isomorphic to the sum-of-products of its code. The isomorphism is witnessed by from and to from the Generic class.

n-ary datatypes

data NP :: (k -> *) -> [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 K a, 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.

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 :: NP f [] 
(:*) :: f x -> NP f xs -> NP f (x : xs) infixr 5 

Instances

HSequence k [k] (NP k) 
HCollapse k [k] (NP k) 
HAp k [k] (NP k) 
HPure k [k] (NP k) 
All * Eq (Map * k f xs) => Eq (NP k f xs) 
(All * Eq (Map * k f xs), All * Ord (Map * k f xs)) => Ord (NP k f xs) 
All * Show (Map * k f xs) => Show (NP k f xs) 
type CollapseTo k [k] (NP k) = [] 
type Prod k [k] (NP k) = NP k 
type AllMap k [k] (NP k) c xs = All k c xs 

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 K a, 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.

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 ]

Constructors

Z :: f x -> NS f (x : xs) 
S :: NS f xs -> NS f (x : xs) 

Instances

HSequence k [k] (NS k) 
HCollapse k [k] (NS k) 
HAp k [k] (NS k) 
All * Eq (Map * k f xs) => Eq (NS k f xs) 
(All * Eq (Map * k f xs), All * Ord (Map * k f xs)) => Ord (NS k f xs) 
All * Show (Map * k f xs) => Show (NS k f xs) 
type CollapseTo k [k] (NS k) = I 
type Prod k [k] (NS k) = NP k 

newtype SOP f xss Source

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 SOP I 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.

Constructors

SOP (NS (NP f) xss) 

Instances

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 

unSOP :: SOP f xss -> NS (NP f) xss Source

Unwrap a sum of products.

newtype POP f xss 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.

Constructors

POP (NP (NP f) xss) 

Instances

HSequence k [[k]] (POP k) 
HCollapse k [[k]] (POP k) 
HAp k [[k]] (POP k) 
HPure k [[k]] (POP k) 
All * Eq (Map * [k] (NP k f) xss) => Eq (POP k f xss) 
(All * Eq (Map * [k] (NP k f) xss), All * Ord (Map * [k] (NP k f) xss)) => Ord (POP k f xss) 
All * Show (Map * [k] (NP k f) xss) => Show (POP k f xss) 
type CollapseTo k [[k]] (POP k) = (:.:) * * [] [] 
type Prod k [[k]] (POP k) = POP k 
type AllMap k [[k]] (POP k) c xs = All2 k c xs 

unPOP :: POP f xss -> NP (NP f) xss Source

Unwrap a product of products.

Metadata

data DatatypeInfo :: [[*]] -> * where Source

Metadata for a datatype.

A value of type DatatypeInfo c contains the information about a datatype that is not contained in Code c. This information consists primarily of the names of the datatype, its constructors, and possibly its record selectors.

The constructor indicates whether the datatype has been declared using newtype or not.

Instances

All * Eq (Map * [*] ConstructorInfo xs) => Eq (DatatypeInfo xs) 
(All * Eq (Map * [*] ConstructorInfo xs), All * Ord (Map * [*] ConstructorInfo xs)) => Ord (DatatypeInfo xs) 
All * Show (Map * [*] ConstructorInfo xs) => Show (DatatypeInfo xs) 

data ConstructorInfo :: [*] -> * where Source

Metadata for a single constructors.

This is indexed by the product structure of the constructor components.

Instances

All * Eq (Map * * FieldInfo xs) => Eq (ConstructorInfo xs) 
(All * Eq (Map * * FieldInfo xs), All * Ord (Map * * FieldInfo xs)) => Ord (ConstructorInfo xs) 
All * Show (Map * * FieldInfo xs) => Show (ConstructorInfo xs) 

data FieldInfo :: * -> * where Source

For records, this functor maps the component to its selector name.

Constructors

FieldInfo :: FieldName -> FieldInfo a 

Instances

class HasDatatypeInfo a where Source

A class of datatypes that have associated metadata.

It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.

You typically don't define instances of this class by hand, but rather derive the class instance automatically. See the documentation of Generic for the options.

Minimal complete definition

Nothing

Instances

HasDatatypeInfo Bool 
HasDatatypeInfo Ordering 
HasDatatypeInfo () 
HasDatatypeInfo FormatAdjustment 
HasDatatypeInfo FormatSign 
HasDatatypeInfo FieldFormat 
HasDatatypeInfo FormatParse 
HasDatatypeInfo DataRep 
HasDatatypeInfo ConstrRep 
HasDatatypeInfo Fixity 
HasDatatypeInfo Version 
HasDatatypeInfo IOMode 
HasDatatypeInfo PatternMatchFail 
HasDatatypeInfo RecSelError 
HasDatatypeInfo RecConError 
HasDatatypeInfo RecUpdError 
HasDatatypeInfo NoMethodError 
HasDatatypeInfo NonTermination 
HasDatatypeInfo NestedAtomically 
HasDatatypeInfo Errno 
HasDatatypeInfo BlockedIndefinitelyOnMVar 
HasDatatypeInfo BlockedIndefinitelyOnSTM 
HasDatatypeInfo Deadlock 
HasDatatypeInfo AssertionFailed 
HasDatatypeInfo AsyncException 
HasDatatypeInfo ArrayException 
HasDatatypeInfo ExitCode 
HasDatatypeInfo BufferMode 
HasDatatypeInfo Newline 
HasDatatypeInfo NewlineMode 
HasDatatypeInfo SeekMode 
HasDatatypeInfo GeneralCategory 
HasDatatypeInfo CChar 
HasDatatypeInfo CSChar 
HasDatatypeInfo CUChar 
HasDatatypeInfo CShort 
HasDatatypeInfo CUShort 
HasDatatypeInfo CInt 
HasDatatypeInfo CUInt 
HasDatatypeInfo CLong 
HasDatatypeInfo CULong 
HasDatatypeInfo CLLong 
HasDatatypeInfo CULLong 
HasDatatypeInfo CFloat 
HasDatatypeInfo CDouble 
HasDatatypeInfo CPtrdiff 
HasDatatypeInfo CSize 
HasDatatypeInfo CWchar 
HasDatatypeInfo CSigAtomic 
HasDatatypeInfo CClock 
HasDatatypeInfo CTime 
HasDatatypeInfo CUSeconds 
HasDatatypeInfo CSUSeconds 
HasDatatypeInfo CIntPtr 
HasDatatypeInfo CUIntPtr 
HasDatatypeInfo CIntMax 
HasDatatypeInfo CUIntMax 
HasDatatypeInfo MaskingState 
HasDatatypeInfo IOException 
HasDatatypeInfo ErrorCall 
HasDatatypeInfo ArithException 
HasDatatypeInfo All 
HasDatatypeInfo Any 
HasDatatypeInfo Lexeme 
HasDatatypeInfo Number 
HasDatatypeInfo [a] 
HasDatatypeInfo (ArgOrder a) 
HasDatatypeInfo (OptDescr a) 
HasDatatypeInfo (ArgDescr a) 
HasDatatypeInfo (Fixed a) 
HasDatatypeInfo (Complex a) 
HasDatatypeInfo (Dual a) 
HasDatatypeInfo (Endo a) 
HasDatatypeInfo (Sum a) 
HasDatatypeInfo (Product a) 
HasDatatypeInfo (First a) 
HasDatatypeInfo (Last a) 
HasDatatypeInfo (Down a) 
HasDatatypeInfo (Maybe a) 
HasDatatypeInfo (I a) 
HasDatatypeInfo (Either a b) 
HasDatatypeInfo (a, b) 
HasDatatypeInfo (Proxy * t) 
Typeable (* -> Constraint) HasDatatypeInfo 
HasDatatypeInfo (a, b, c) 
HasDatatypeInfo (K * a b) 
HasDatatypeInfo (a, b, c, d) 
HasDatatypeInfo (a, b, c, d, e) 
HasDatatypeInfo ((:.:) * * f g p) 
HasDatatypeInfo (a, b, c, d, e, f) 
HasDatatypeInfo (a, b, c, d, e, f, g) 
HasDatatypeInfo (a, b, c, d, e, f, g, h) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

type DatatypeName = String Source

The name of a datatype.

type ModuleName = String Source

The name of a module.

type ConstructorName = String Source

The name of a data constructor.

type FieldName = String Source

The name of a field / record selector.

data Associativity :: *

Datatype to represent the associativity of a constructor

Instances

Eq Associativity 
Ord Associativity 
Read Associativity 
Show Associativity 
Generic Associativity 
type Rep Associativity = D1 D1Associativity ((:+:) (C1 C1_0Associativity U1) ((:+:) (C1 C1_1Associativity U1) (C1 C1_2Associativity U1))) 

type Fixity = Int Source

The fixity of an infix constructor.

Combinators

Constructing products

class HPure h where Source

A generalization of pure or return to higher kinds.

Methods

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 xs
hpure, 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 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  :: (SingI xs,  All  c xs ) => Proxy c -> (forall a. c a => f a) -> NP  f xs
hcpure, cpure_POP :: (SingI xss, All2 c xss) => Proxy c -> (forall a. c a => f a) -> POP f xss

Instances

HPure k [[k]] (POP k) 
HPure k [k] (NP k) 
Typeable (((k -> *) -> k -> *) -> Constraint) (HPure k k) 

Application

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

Lifted functions.

Constructors

Fn 

Fields

apFn :: f a -> g a
 

Instances

Typeable ((k -> *) -> (k -> *) -> k -> *) ((-.->) k) 

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 
type Prod k [k] (NP k) = NP k 
type Prod k [[k]] (SOP k) = POP k 
type Prod k [k] (NS k) = NP k 

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 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 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) 
HAp k [k] (NP k) 
HAp k [[k]] (SOP k) 
HAp k [k] (NS k) 
Typeable (((k -> *) -> k -> *) -> Constraint) (HAp k k) 

Lifting / mapping

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' xs
hliftA, liftA_NS  :: SingI xs  => (forall a. f a -> f' a) -> NS  f xs  -> NS  f' xs
hliftA, liftA_POP :: SingI xss => (forall a. f a -> f' a) -> POP f xss -> POP f' xss
hliftA, 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'' xs
hliftA2, liftA2_NS  :: SingI xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NS  f' xs  -> NS  f'' xs
hliftA2, liftA2_POP :: SingI xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> POP f' xss -> POP f'' xss
hliftA2, 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''' xs
hliftA3, 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''' xs
hliftA3, 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''' xs
hliftA3, 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

Variant of hliftA that takes a constrained function.

Specification:

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

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

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 -> K (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))))]

Dealing with All c

data AllDict c xs where Source

Dictionary for a constraint for all elements of a type-level list.

A value of type AllDict c xs captures the constraint All c xs.

Constructors

AllDictC :: (SingI xs, All c xs) => AllDict c xs 

Instances

Typeable ((k -> Constraint) -> [k] -> *) (AllDict k) 

allDict_NP :: forall c xss. (All2 c xss, SingI xss) => Proxy c -> NP (AllDict c) xss Source

Construct a product of dictionaries for a type-level list of lists.

The structure of the product matches the outer list, the dictionaries contained are AllDict-dictionaries for the inner list.

hcliftA' :: (All2 c xss, SingI xss, Prod h ~ NP, HAp h) => Proxy c -> (forall xs. (SingI xs, 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, SingI xss) => Proxy c -> (forall xs. (SingI xs, All c xs) => f xs -> f' xs) -> NP f xss -> NP f' xss
hcliftA' :: (All2 c xss, SingI xss) => Proxy c -> (forall xs. (SingI xs, All c xs) => f xs -> f' xs) -> NS f xss -> NS f' xss

hcliftA2' :: (All2 c xss, SingI xss, Prod h ~ NP, HAp h) => Proxy c -> (forall xs. (SingI xs, All c xs) => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss Source

Like hcliftA', but for binary functions.

hcliftA3' :: (All2 c xss, SingI xss, Prod h ~ NP, HAp h) => Proxy c -> (forall xs. (SingI xs, 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

Like hcliftA', but for ternay functions.

Collapsing

type family CollapseTo h :: * -> * Source

Maps products to lists, and sums to identities.

Instances

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.

Methods

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 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) 
HCollapse k [k] (NP k) 
HCollapse k [[k]] (SOP k) 
HCollapse k [k] (NS k) 
Typeable (((k -> *) -> k -> *) -> Constraint) (HCollapse k k) 

Sequencing

class HAp h => HSequence h where Source

A generalization of sequenceA.

Methods

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)

Instances

HSequence k [[k]] (POP k) 
HSequence k [k] (NP k) 
HSequence k [[k]] (SOP k) 
HSequence k [k] (NS k) 
Typeable (((k -> *) -> k -> *) -> Constraint) (HSequence k k) 

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.

Partial operations

fromList :: SingI xs => [a] -> Maybe (NP (K a) 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.

Utilities

Basic functors

newtype K a b Source

The constant type functor.

Like Constant, but kind-polymorphic in its second argument and with a shorter name.

Constructors

K a 

Instances

Functor (K * a) 
Monoid a => Applicative (K * a) 
Foldable (K * a) 
Traversable (K * a) 
Show a => Show (K k a b) 
Generic (K k a b) 
HasDatatypeInfo (K * a b) 
Generic (K * a b) 
type Rep (K k a b) 
type Code (K * a0 b0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) 

unK :: K a b -> a Source

Extract the contents of a K value.

newtype I a Source

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 

Instances

Monad I 
Functor I 
Applicative I 
Foldable I 
Traversable I 
Show a => Show (I a) 
Generic (I a) 
HasDatatypeInfo (I a) 
Generic (I a) 
Typeable (k -> I k) (I k) 
type Rep (I a) 
type Code (I a0) = (:) [*] ((:) * a0 ([] *)) ([] [*]) 

unI :: I a -> a Source

Extract the contents of an I value.

newtype (f :.: g) p infixr 7 Source

Composition of functors.

Like Compose, but kind-polymorphic and with a shorter name.

Constructors

Comp (f (g p)) 

Instances

(Functor f, Functor g) => Functor ((:.:) * * f g) 
Show (f (g p)) => Show ((:.:) l k f g p) 
Generic ((:.:) l k f g p) 
HasDatatypeInfo ((:.:) * * f g p) 
Generic ((:.:) * * f g p) 
type Rep ((:.:) l k f g p) 
type Code ((:.:) * * f0 g0 p0) = (:) [*] ((:) * (f0 (g0 p0)) ([] *)) ([] [*]) 

unComp :: (f :.: g) p -> f (g p) Source

Extract the contents of a Comp value.

Mapping constraints

type family All c xs :: Constraint Source

Require a constraint for every element of a list.

If you have a datatype that is indexed over a type-level list, then you can use All to indicate that all elements of that type-level list must satisfy a given constraint.

Example: The constraint

All Eq '[ Int, Bool, Char ]

is equivalent to the constraint

(Eq Int, Eq Bool, Eq Char)

Example: A type signature such as

f :: All Eq xs => NP I xs -> ...

means that f can assume that all elements of the n-ary product satisfy Eq.

Instances

type All k c ([] k) = () 
type All k c ((:) k x xs) = (c x, All k c xs) 

type family All2 c xs :: Constraint Source

Require a constraint for every element of a list of lists.

If you have a datatype that is indexed over a type-level list of lists, then you can use All2 to indicate that all elements of the innert lists must satisfy a given constraint.

Example: The constraint

All2 Eq '[ '[ Int ], '[ Bool, Char ] ]

is equivalent to the constraint

(Eq Int, Eq Bool, Eq Char)

Example: A type signature such as

f :: All2 Eq xss => SOP I xs -> ...

means that f can assume that all elements of the sum of product satisfy Eq.

Instances

type All2 k c ([] [k]) = () 
type All2 k c ((:) [k] x xs) = (All k c x, All2 k c xs) 

type family Map f xs :: [l] Source

A type-level map.

Instances

type Map k k1 f ([] k1) = [] k 
type Map k k1 f ((:) k1 x xs) = (:) k (f x) (Map k k1 f xs) 

type family AllMap h c xs :: Constraint Source

A generalization of All and All2.

The family AllMap expands to All or All2 depending on whether the argument is indexed by a list or a list of lists.

Instances

type AllMap k [[k]] (POP k) c xs = All2 k c xs 
type AllMap k [k] (NP k) c xs = All k c xs 

Singletons

data family Sing a Source

Explicit singleton.

A singleton can be used to reveal the structure of a type argument that the function is quantified over.

The family Sing should have at most one instance per kind, and there should be a matching instance for SingI.

Instances

Eq (Sing [k] xs) 
Eq (Sing * x) 
Ord (Sing [k] xs) 
Ord (Sing * x) 
Show (Sing [k] xs) 
Show (Sing * x) 
data Sing * = SStar

Singleton for types of kind *.

For types of kind *, we explicitly don't want to reveal more type analysis. Even functions that have a Sing constraint should still be parametric in everything that is of kind *.

data Sing [k] where

Singleton for type-level lists.

class SingI a where Source

Implicit singleton.

A singleton can be used to reveal the structure of a type argument that the function is quantified over.

The class SingI should have instances that match the family instances for Sing.

Methods

sing :: Sing a Source

Get hold of the explicit singleton (that one can then pattern match on).

Instances

SingI * x 
SingI [k] ([] k) 
(SingI k x, SingI [k] xs) => SingI [k] ((:) k x xs) 

Shape of type-level lists

data Shape :: [k] -> * where Source

Occassionally it is useful to have an explicit, term-level, representation of type-level lists (esp because of https://ghc.haskell.org/trac/ghc/ticket/9108)

Constructors

ShapeNil :: Shape [] 
ShapeCons :: SingI xs => Shape xs -> Shape (x : xs) 

Instances

Eq (Shape k xs) 
Ord (Shape k xs) 
Show (Shape k xs) 

shape :: forall xs. SingI xs => Shape xs Source

The shape of a type-level list.

lengthSing :: forall xs. SingI xs => Proxy xs -> Int Source

The length of a type-level list.

Re-exports

data Proxy t :: k -> *

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 
Functor (Proxy *) 
Applicative (Proxy *) 
Foldable (Proxy *) 
Traversable (Proxy *) 
Bounded (Proxy k s) 
Enum (Proxy k s) 
Eq (Proxy k s) 
Data t => Data (Proxy * t) 
Ord (Proxy k s) 
Read (Proxy k s) 
Show (Proxy k s) 
Ix (Proxy k s) 
Generic (Proxy * t) 
Monoid (Proxy * s) 
HasDatatypeInfo (Proxy * t) 
Generic (Proxy * t) 
Typeable (k -> *) (Proxy k) 
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1) 
type Code (Proxy * t0) = (:) [*] ([] *) ([] [*])