Copyright | (c) 2008--2010 Universiteit Utrecht |
---|---|
License | BSD3 |
Maintainer | generics@haskell.org |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module is the base of the multirec library. It defines the view of a family of datatypes: All the datatypes of the family are represented as indexed functors that are built up from the structure types defined in this module. Furthermore, in order to use the library for a family, conversion functions have to be defined between the original datatypes and their representation. The type class that holds these conversion functions are also defined here.
- data I xi r ix = I {
- unI :: r xi
- data K a r ix = K {
- unK :: a
- data U r ix = U
- data (f :+: g) r ix
- data (f :*: g) r ix = (f r ix) :*: (g r ix)
- data (f :>: ix) r ix' where
- unTag :: (f :>: ix) r ix -> f r ix
- data (f :.: g) r ix = D {
- unD :: f (g r ix)
- data C c f r ix where
- unC :: C c f r ix -> f r ix
- module Generics.MultiRec.Constructor
- newtype I0 a = I0 {
- unI0 :: a
- newtype K0 a b = K0 {
- unK0 :: a
- type family PF phi :: (* -> *) -> * -> *
- class El phi ix where
- proof :: phi ix
- class Fam phi where
- index :: El phi ix => phi ix
- module Generics.MultiRec.TEq
- class EqS phi where
Structure types
Represents recursive positions. The first argument indicates which type to recurse on.
El phi xi => HFunctor phi (I xi) Source | |
El phi xi => HEq phi (I xi) Source | |
El phi xi => HShow phi (I xi) Source | |
El phi xi => HReadPrec phi (I xi) Source | |
(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) Source | |
ConNames (I a) Source | |
Fold (I xi) Source | |
Fold (I xi) Source | |
CountAtoms (I xi) Source | |
Functor f => Fold ((:.:) f (I xi)) Source | |
Fold g => Fold ((:*:) (I xi) g) Source | |
Fold g => Fold ((:*:) (I xi) g) Source | |
type Alg (I xi) r = r -> r Source | For an identity, we turn the recursive result into a final result. Note that the index can change. |
type Comp (I xi) r ix = r xi Source | |
type Alg (I xi) r ix = r xi -> r ix Source | For an identity, we turn the recursive result into a final result. Note that the index can change. |
type Alg ((:*:) (I xi) g) r = r -> Alg g r Source | For a product where the left hand side is an identity, we take the recursive result as an additional argument. |
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix Source |
Represents constant types that do not belong to the family.
HFunctor phi (K x) Source | |
Eq a => HEq phi (K a) Source | For constant types, we make use of the standard equality function. |
Show a => HShow phi (K a) Source | For constant types, we make use of the standard show function. |
Read a => HReadPrec phi (K a) Source | |
(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) Source | |
ConNames (K x) Source | |
Fold (K a) Source | |
Fold (K a) Source | |
CountAtoms (K a) Source | |
Fold g => Fold ((:*:) (K a) g) Source | |
Fold g => Fold ((:*:) (K a) g) Source | |
type Alg (K a) r = a -> r Source | For a constant, we take the constant value to a result. |
type Comp (K a) r ix = a Source | |
type Alg (K a) r ix = a -> r ix Source | For a constant, we take the constant value to a result. |
type Alg ((:*:) (K a) g) r = a -> Alg g r Source | For a product where the left hand side is a constant, we take the value as an additional argument. |
Represents constructors without fields.
ConNames U Source | |
Fold U Source | |
Fold U Source | |
HFunctor phi U Source | |
HEq phi U Source | |
HShow phi U Source | |
HReadPrec phi U Source | |
Constructor c => HReadPrec phi (C c U) Source | |
type Alg U r = r Source | For a unit, no arguments are available. |
type Alg U r ix = r ix Source | For a unit, no arguments are available. |
data (f :+: g) r ix infixr 5 Source
Represents sums (choices between constructors).
(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:+:) f g) Source | |
(HEq phi f, HEq phi g) => HEq phi ((:+:) f g) Source | |
(HShow phi f, HShow phi g) => HShow phi ((:+:) f g) Source | |
(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:+:) f g) Source | |
(ConNames f, ConNames g) => ConNames ((:+:) f g) Source | |
(Fold f, Fold g) => Fold ((:+:) f g) Source | |
(Fold f, Fold g) => Fold ((:+:) f g) Source | |
type Alg ((:+:) f g) r = (Alg f r, Alg g r) Source | For a sum, the algebra is a pair of two algebras. |
type Alg ((:+:) f g) r ix = (Alg f r ix, Alg g r ix) Source | For a sum, the algebra is a pair of two algebras. |
data (f :*: g) r ix infixr 7 Source
Represents products (sequences of fields of a constructor).
(f r ix) :*: (g r ix) infixr 7 |
(HFunctor phi f, HFunctor phi g) => HFunctor phi ((:*:) f g) Source | |
(HEq phi f, HEq phi g) => HEq phi ((:*:) f g) Source | |
(HShow phi f, HShow phi g) => HShow phi ((:*:) f g) Source | |
(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) Source | |
(HReadPrec phi f, HReadPrec phi g) => HReadPrec phi ((:*:) f g) Source | |
ConNames ((:*:) f g) Source | |
Fold g => Fold ((:*:) (K a) g) Source | |
Fold g => Fold ((:*:) (I xi) g) Source | |
Fold g => Fold ((:*:) (K a) g) Source | |
Fold g => Fold ((:*:) (I xi) g) Source | |
(CountAtoms f, CountAtoms g) => CountAtoms ((:*:) f g) Source | |
type Alg ((:*:) (K a) g) r = a -> Alg g r Source | For a product where the left hand side is a constant, we take the value as an additional argument. |
type Alg ((:*:) (I xi) g) r = r -> Alg g r Source | For a product where the left hand side is an identity, we take the recursive result as an additional argument. |
type Alg ((:*:) f g) r ix = Comp f r ix -> Alg g r ix Source | For a product where the left hand side is a constant, we take the value as an additional argument. |
data (f :>: ix) r ix' where infix 6 Source
Is used to indicate the type that a particular constructor injects to.
HFunctor phi f => HFunctor phi ((:>:) f ix) Source | |
HEq phi f => HEq phi ((:>:) f ix) Source | |
HShow phi f => HShow phi ((:>:) f ix) Source | |
(HReadPrec phi f, EqS phi, El phi ix) => HReadPrec phi ((:>:) f ix) Source | |
ConNames f => ConNames ((:>:) f ix) Source | |
Fold f => Fold ((:>:) f xi) Source | |
Fold f => Fold ((:>:) f xi) Source | |
type Alg ((:>:) f xi) r = Alg f r Source | Tags are ignored. |
type Alg ((:>:) f xi) r ix = Alg f r xi Source | A tag changes the index of the final result. |
Represents composition with functors of kind * -> *.
(Traversable f, HFunctor phi g) => HFunctor phi ((:.:) f g) Source | |
(Eq1 f, HEq phi g) => HEq phi ((:.:) f g) Source | |
(Show1 f, Traversable f, HShow phi g) => HShow phi ((:.:) f g) Source | |
(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) Source | |
(Read1 f, HReadPrec phi g) => HReadPrec phi ((:.:) f g) Source | |
ConNames ((:.:) f g) Source | |
Functor f => Fold ((:.:) f (I xi)) Source | |
type Comp ((:.:) f g) r ix = f (Comp g r ix) Source | |
type Alg ((:.:) f (I xi)) r ix = f (r xi) -> r ix Source |
Represents constructors.
(Constructor c, HFunctor phi f) => HFunctor phi (C c f) Source | |
(Constructor c, HEq phi f) => HEq phi (C c f) Source | |
(Constructor c, HShow phi f) => HShow phi (C c f) Source | |
(Constructor c, CountAtoms ((:*:) f g), HReadPrec phi f, HReadPrec phi g) => HReadPrec phi (C c ((:*:) f g)) Source | |
(Constructor c, HReadPrec phi ((:.:) f g)) => HReadPrec phi (C c ((:.:) f g)) Source | |
(Constructor c, HReadPrec phi (K a)) => HReadPrec phi (C c (K a)) Source | |
(Constructor c, HReadPrec phi (I xi)) => HReadPrec phi (C c (I xi)) Source | |
Constructor c => HReadPrec phi (C c U) Source | |
Constructor c => ConNames (C c f) Source | |
Fold f => Fold (C c f) Source | |
Fold f => Fold (C c f) Source | |
type Alg (C c f) r = Alg f r Source | Constructors are ignored. |
type Alg (C c f) r ix = Alg f r ix Source | Constructors are ignored. |
Constructor information
Unlifted variants
Indexed families
type family PF phi :: (* -> *) -> * -> * Source
Type family describing the pattern functor of a family.
Class that contains the shallow conversion functions for a family.
Equality for indexed families
module Generics.MultiRec.TEq