regular-0.2.4: Generic programming library for regular datatypes.

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.Regular.Base

Contents

Description

Summary: Types for structural representation.

Synopsis

Functorial structural representation types

newtype K a r Source

Structure type for constant values.

Constructors

K 

Fields

unK :: a
 

Instances

Functor (K a) 
ConNames (K a) 
Crush (K a) 
Unfold (K a) 
Fold (K a) 
GMap (K a) 
LRBase a => LR (K a) 
DeepSeq a => Seq (K a)

For constants we rely on the |DeepSeq| class.

Eq a => Zip (K a) 
Eq a => Eq (K a) 
Read a => Read (K a) 
CountAtoms (K a) 
Show a => Show (K a) 
Fold g => Fold (:*: (K a) g) 
(Constructor c, Read (K a)) => Read (C c (K a)) 

newtype I r Source

Structure type for recursive values.

Constructors

I 

Fields

unI :: r
 

Instances

Functor I 
ConNames I 
Crush I 
Unfold I 
Fold I 
GMap I 
LR I 
Seq I 
Zip I 
Eq I 
Read I 
CountAtoms I 
Show I 
Fold g => Fold (:*: I g) 
(Constructor c, Read I) => Read (C c I) 

data U r Source

Structure type for empty constructors.

Constructors

U 

Instances

data (f :+: g) r Source

Structure type for alternatives in a type.

Constructors

L (f r) 
R (g r) 

Instances

(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) 
(Seq f, Seq g) => Seq (:+: 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) 

data (f :*: g) r Source

Structure type for fields of a constructor.

Constructors

(f r) :*: (g r) 

Instances

(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) 
(Seq f, Seq g) => Seq (:*: f g) 
(Zip f, Zip g) => Zip (:*: f g) 
(Eq f, Eq g) => Eq (:*: f g) 
(Constructor c, CountAtoms (:*: f 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) 

data C c f r Source

Structure type to store the name of a constructor.

Constructors

C 

Fields

unC :: f r
 

Instances

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) 
Seq f => Seq (C c f) 
Zip f => Zip (C c f) 
Eq f => Eq (C c f) 
(Constructor c, CountAtoms (:*: f 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) 

data S l f r Source

Structure type to store the name of a record selector.

Constructors

S 

Fields

unS :: f r
 

Instances

Functor f => Functor (S c 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) 
Seq f => Seq (S s f) 
Zip f => Zip (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.

Methods

conName :: t c (f :: * -> *) r -> StringSource

conFixity :: t c (f :: * -> *) r -> FixitySource

conIsRecord :: t c (f :: * -> *) r -> BoolSource

data Fixity Source

Datatype to represent the fixity of a constructor. An infix declaration directly corresponds to an application of Infix.

Constructors

Prefix 
Infix Associativity Int 

class Selector s whereSource

Methods

selName :: t s (f :: * -> *) r -> StringSource

Fixed-point type

newtype Fix f Source

The well-known fixed-point type.

Constructors

In 

Fields

out :: f (Fix f)
 

Type class capturing the structural representation of a type and the corresponding embedding-projection pairs

class Regular a whereSource

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.

Methods

from :: a -> PF a aSource

to :: PF a a -> aSource

type family PF a :: * -> *Source

The type family PF represents the pattern functor of a datatype.

To be able to use the generic functions, the user is required to provide an instance of this type family.