multirec-0.3: Generic programming for families of recursive datatypesSource codeContentsIndex
Generics.MultiRec.Base
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Structure types
Constructor information
Unlifted variants
Indexed families
Equality for indexed families
Description
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.
Synopsis
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
= L (f r ix)
| R (g r ix)
data (f :*: g) r ix = (f r ix) :*: (g r ix)
data f :>: ix where
Tag :: f r ix -> (f :>: ix) r ix
unTag :: (f :>: ix) r ix -> f r ix
data C c f r ix where
C :: f r ix -> C c f r ix
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
from :: phi ix -> ix -> PF phi I0 ix
to :: phi ix -> PF phi I0 ix -> ix
index :: El phi ix => phi ix
module Generics.MultiRec.TEq
class EqS phi where
eqS :: phi ix -> phi ix' -> Maybe (ix :=: ix')
Structure types
data I xi r ix Source
Represents recursive positions. The first argument indicates which type to recurse on.
Constructors
I
unI :: r xi
show/hide Instances
El phi xi => HFunctor phi (I xi)
El phi xi => HEq phi (I xi)
El phi xi => HShow phi (I xi)
ConNames (I a)
Fold (I xi)
Fold (I xi)
data K a r ix Source
Represents constant types that do not belong to the family.
Constructors
K
unK :: a
show/hide Instances
HFunctor phi (K x)
Eq a => HEq phi (K a)
Show a => HShow phi (K a)
ConNames (K x)
Fold (K a)
Fold (K a)
data U r ix Source
Represents constructors without fields.
Constructors
U
show/hide Instances
data (f :+: g) r ix Source
Represents sums (choices between constructors).
Constructors
L (f r ix)
R (g r ix)
show/hide Instances
(HFunctor phi f, HFunctor phi g) => HFunctor phi (f :+: g)
(HEq phi f, HEq phi g) => HEq phi (f :+: g)
(HShow phi f, HShow phi g) => HShow phi (f :+: g)
(ConNames f, ConNames g) => ConNames (f :+: g)
(Fold f, Fold g) => Fold (f :+: g)
(Fold f, Fold g) => Fold (f :+: g)
data (f :*: g) r ix Source
Represents products (sequences of fields of a constructor).
Constructors
(f r ix) :*: (g r ix)
show/hide Instances
(HFunctor phi f, HFunctor phi g) => HFunctor phi (f :*: g)
(HEq phi f, HEq phi g) => HEq phi (f :*: g)
(HShow phi f, HShow phi g) => HShow phi (f :*: g)
ConNames (f :*: g)
Fold g => Fold (K a :*: g)
Fold g => Fold (I xi :*: g)
Fold g => Fold (K a :*: g)
Fold g => Fold (I xi :*: g)
data f :>: ix whereSource
Is used to indicate the type that a particular constructor injects to.
Constructors
Tag :: f r ix -> (f :>: ix) r ix
show/hide Instances
HFunctor phi f => HFunctor phi (f :>: ix)
HEq phi f => HEq phi (f :>: ix)
HShow phi f => HShow phi (f :>: ix)
ConNames f => ConNames (f :>: ix)
Fold f => Fold (f :>: xi)
Fold f => Fold (f :>: xi)
unTag :: (f :>: ix) r ix -> f r ixSource
Destructor for '(:>:)'.
data C c f r ix whereSource
Represents constructors.
Constructors
C :: f r ix -> C c f r ix
show/hide Instances
(Constructor c, HFunctor phi f) => HFunctor phi (C c f)
(Constructor c, HEq phi f) => HEq phi (C c f)
(Constructor c, HShow phi f) => HShow phi (C c f)
Constructor c => ConNames (C c f)
Fold f => Fold (C c f)
Fold f => Fold (C c f)
unC :: C c f r ix -> f r ixSource
Destructor for C.
Constructor information
module Generics.MultiRec.Constructor
Unlifted variants
newtype I0 a Source
Unlifted version of I.
Constructors
I0
unI0 :: a
show/hide Instances
newtype K0 a b Source
Unlifted version of K.
Constructors
K0
unK0 :: a
show/hide Instances
Indexed families
type family PF phi :: (* -> *) -> * -> *Source
Type family describing the pattern functor of a family.
class El phi ix whereSource
Class for the members of a family.
Methods
proof :: phi ixSource
class Fam phi whereSource
Class that contains the shallow conversion functions for a family.
Methods
from :: phi ix -> ix -> PF phi I0 ixSource
to :: phi ix -> PF phi I0 ix -> ixSource
index :: El phi ix => phi ixSource
For backwards-compatibility: a synonym for proof.
Equality for indexed families
module Generics.MultiRec.TEq
class EqS phi whereSource
Semi-decidable equality for types of a family.
Methods
eqS :: phi ix -> phi ix' -> Maybe (ix :=: ix')Source
Produced by Haddock version 2.4.2