multirec-0.2: Generic programming with systems of recursive datatypesSource codeContentsIndex
Generics.MultiRec.Base
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Contents
Structure types
Constructor information
Unlifted variants
Indexed systems
Description
This module is the base of the multirec library. It defines the view of a system of datatypes: All the datatypes of the system 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 system, 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 where
I :: Ix s xi => r xi -> I xi s r ix
unI :: I xi s r ix -> r xi
data K a s r ix = K {
unK :: a
}
data U s r ix = U
data (f :+: g) s r ix
= L (f s r ix)
| R (g s r ix)
data (f :*: g) s r ix = (f s r ix) :*: (g s r ix)
data :>: where
Tag :: f s r ix -> (f :>: ix) s r ix
unTag :: (f :>: ix) s r ix -> f s r ix
data C c f s r ix where
C :: Constructor c => f s r ix -> C c f s r ix
unC :: C c f s r ix -> f s r ix
module Generics.MultiRec.Constructor
newtype I0 a = I0 {
unI0 :: a
}
newtype K0 a b = K0 {
unK0 :: a
}
type family PF s :: (* -> *) -> (* -> *) -> * -> *
type Str s ix = PF s s I0 ix
class Ix s ix where
from_ :: ix -> Str s ix
to_ :: Str s ix -> ix
from :: pfs ~ PF s => ix -> pfs s I0 ix
to :: pfs ~ PF s => pfs s I0 ix -> ix
index :: s ix
Structure types
data I whereSource
Represents recursive positions. The first argument indicates which type (within the system) to recurse on.
Constructors
I :: Ix s xi => r xi -> I xi s r ix
show/hide Instances
ConNames (I a)
HFunctor (I xi)
Fold (I xi)
Fold (I xi)
HEq (I xi)
HShow (I xi)
unI :: I xi s r ix -> r xiSource
Destructor for I.
data K a s r ix Source
Represents constant types that do not belong to the system.
Constructors
K
unK :: a
show/hide Instances
ConNames (K x)
HFunctor (K x)
Fold (K a)
Fold (K a)
Eq x => HEq (K x)
Show x => HShow (K x)
data U s r ix Source
Represents constructors without fields.
Constructors
U
show/hide Instances
data (f :+: g) s r ix Source
Represents sums (choices between constructors).
Constructors
L (f s r ix)
R (g s r ix)
show/hide Instances
(ConNames f, ConNames g) => ConNames (f :+: g)
(HFunctor f, HFunctor g) => HFunctor (f :+: g)
(Fold f, Fold g) => Fold (f :+: g)
(Fold f, Fold g) => Fold (f :+: g)
(HEq f, HEq g) => HEq (f :+: g)
(HShow f, HShow g) => HShow (f :+: g)
data (f :*: g) s r ix Source
Represents products (sequences of fields of a constructor).
Constructors
(f s r ix) :*: (g s r ix)
show/hide Instances
ConNames (f :*: g)
(HFunctor f, HFunctor g) => HFunctor (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)
(HEq f, HEq g) => HEq (f :*: g)
(HShow f, HShow g) => HShow (f :*: g)
data :>: whereSource
Is used to indicate the type (within the system) that a particular constructor injects to.
Constructors
Tag :: f s r ix -> (f :>: ix) s r ix
show/hide Instances
ConNames f => ConNames (f :>: ix)
HFunctor f => HFunctor (f :>: ix)
Fold f => Fold (f :>: xi)
Fold f => Fold (f :>: xi)
HEq f => HEq (f :>: ix)
HShow f => HShow (f :>: ix)
unTag :: (f :>: ix) s r ix -> f s r ixSource
Destructor for '(:>:)'.
data C c f s r ix whereSource
Represents constructors.
Constructors
C :: Constructor c => f s r ix -> C c f s r ix
show/hide Instances
Constructor c => ConNames (C c f)
HFunctor f => HFunctor (C c f)
Fold f => Fold (C c f)
Fold f => Fold (C c f)
HEq f => HEq (C c f)
HShow f => HShow (C c f)
unC :: C c f s r ix -> f s 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 systems
type family PF s :: (* -> *) -> (* -> *) -> * -> *Source
Type family describing the pattern functor of a system.
type Str s ix = PF s s I0 ixSource
class Ix s ix whereSource
Methods
from_ :: ix -> Str s ixSource
to_ :: Str s ix -> ixSource
from :: pfs ~ PF s => ix -> pfs s I0 ixSource
Some functions need to have their types desugared in order to make programs that use them typable. Desugaring consists in transforming `inline' type family applications into equality constraints. This is a strangeness in current versions of GHC that hopefully will be fixed sometime in the future.
to :: pfs ~ PF s => pfs s I0 ix -> ixSource
index :: s ixSource
Produced by Haddock version 2.4.2