Portability | non-portable |
---|---|
Stability | experimental |
Maintainer | generics@haskell.org |
Safe Haskell | Safe-Inferred |
Summary: Types for structural representation.
- newtype K a r = K {
- unK :: a
- newtype I r = I {
- unI :: r
- data U r = U
- data (f :+: g) r
- data (f :*: g) r = (f r) :*: (g r)
- data C c f r = C {
- unC :: f r
- data S l f r = S {
- unS :: f r
- class Constructor c where
- data Fixity
- = Prefix
- | Infix Associativity Int
- data Associativity
- class Selector s where
- newtype Fix f = In {}
- class Regular a where
- type family PF a :: * -> *
Functorial structural representation types
Structure type for constant values.
Structure type for recursive values.
Structure type for empty constructors.
Structure type for alternatives in a type.
(Functor f, Functor g) => Functor (:+: f g) | |
(ConNames f, ConNames g) => ConNames (:+: f g) | |
(Crush f, Crush g) => Crush (:+: f g) | |
(Unfold f, Unfold g) => Unfold (:+: f g) | |
(Fold f, Fold g) => Fold (:+: f g) | |
(GMap f, GMap g) => GMap (:+: f g) | |
(LR f, LR g) => LR (:+: f g) | |
(Zip f, Zip g) => Zip (:+: f g) | |
(Eq f, Eq g) => Eq (:+: f g) | |
(Read f, Read g) => Read (:+: f g) | |
(Show f, Show g) => Show (:+: f g) |
Structure type for fields of a constructor.
(f r) :*: (g r) |
(Functor f, Functor g) => Functor (:*: f g) | |
(ConNames f, ConNames g) => ConNames (:*: f g) | |
(Crush f, Crush g) => Crush (:*: f g) | |
(Unfold f, Unfold g) => Unfold (:*: f g) | |
Fold g => Fold (:*: I g) | |
Fold g => Fold (:*: (K a) g) | |
(GMap f, GMap g) => GMap (:*: f g) | |
(LR f, LR g) => LR (:*: f g) | |
(Zip f, Zip g) => Zip (:*: f g) | |
(Eq f, Eq g) => Eq (:*: f g) | |
(Constructor c, CountAtoms f, CountAtoms g, Read f, Read g) => Read (C c (:*: f g)) | |
(Read f, Read g) => Read (:*: f g) | |
(CountAtoms f, CountAtoms g) => CountAtoms (:*: f g) | |
(Show f, Show g) => Show (:*: f g) |
Structure type to store the name of a constructor.
Functor f => Functor (C c f) | |
(ConNames f, Constructor c) => ConNames (C c f) | |
Crush f => Crush (C c f) | |
Unfold f => Unfold (C c f) | |
Fold f => Fold (C c f) | |
GMap f => GMap (C c f) | |
LR f => LR (C c f) | |
Zip f => Zip (C c f) | |
Eq f => Eq (C c f) | |
(Constructor c, CountAtoms f, CountAtoms g, Read f, Read g) => Read (C c (:*: f g)) | |
(Constructor c, Read (S s f)) => Read (C c (S s f)) | |
(Constructor c, Read (K a)) => Read (C c (K a)) | |
(Constructor c, Read I) => Read (C c I) | |
Constructor c => Read (C c U) | |
(Constructor c, Show f) => Show (C c f) |
Structure type to store the name of a record selector.
Functor f => Functor (S c f) | |
ConNames (S s f) | |
Crush f => Crush (S s f) | |
Unfold f => Unfold (S s f) | |
Fold f => Fold (S s f) | |
GMap f => GMap (S s f) | |
LR f => LR (S s f) | |
Zip f => Zip (S s f) | |
Eq f => Eq (S s f) | |
(Selector s, Read f) => Read (S s f) | |
(Constructor c, Read (S s f)) => Read (C c (S s f)) | |
CountAtoms f => CountAtoms (S s f) | |
(Selector s, Show f) => Show (S s f) |
class Constructor c whereSource
Class for datatypes that represent data constructors.
For non-symbolic constructors, only conName
has to be defined.
The weird argument is supposed to be instantiated with C
from
base, hence the complex kind.
Datatype to represent the fixity of a constructor. An infix declaration
directly corresponds to an application of Infix
.
data Associativity Source
Fixed-point type
Type class capturing the structural representation of a type and the corresponding embedding-projection pairs
The type class Regular
captures the structural representation of a
type and the corresponding embedding-projection pairs.
To be able to use the generic functions, the user is required to provide an instance of this type class.