regular-0.3.4.4: Generic programming library for regular datatypes.

Copyright(c) 2008 Universiteit Utrecht
LicenseBSD3
Maintainergenerics@haskell.org
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell98

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) 
Eq a => Zip (K a) 
Eq a => Eq (K a) 
Read a => Read (K a) 
Show a => Show (K a) 
Fold g => Fold ((:*:) (K a) g) 
(Constructor c, Read (K a)) => Read (C c (K a)) 
type CoAlg (K a) s = a

For a constant, we produce a constant value as a result.

type Alg (K a) r = a -> r

For a constant, we take the constant value to a result.

type Alg ((:*:) (S s (K a)) g) r = a -> Alg g r 
type Alg ((:*:) (K a) g) r = a -> Alg g r

For a product where the left hand side is a constant, we take the value as an additional argument.

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 
Zip I 
Eq I 
Read I 
Show I 
Fold g => Fold ((:*:) I g) 
(Constructor c, Read I) => Read (C c I) 
type CoAlg I s = s

For an identity, we produce a new seed to create the recursive result.

type Alg I r = r -> r

For an identity, we turn the recursive result into a final result.

type Alg ((:*:) I g) r = r -> Alg g r

For a product where the left hand side is an identity, we take the recursive result as an additional argument.

data U r Source

Structure type for empty constructors.

Constructors

U 

Instances

Functor U 
ConNames U 
Crush U 
Unfold U 
Fold U 
GMap U 
LR U 
Zip U 
Eq U 
Read U 
Show U 
Constructor c => Read (C c U) 
type CoAlg U s = ()

Units can only produce units, so we use the singleton type to encode the lack of choice.

type Alg U r = r

For a unit, no arguments are available.

data (f :+: g) r infixr 6 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) 
(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) 
type CoAlg ((:+:) f g) s = Either (CoAlg f s) (CoAlg g s)

For a sum, the coalgebra produces either the left or the right side.

type Alg ((:+:) f g) r = (Alg f r, Alg g r)

For a sum, the algebra is a pair of two algebras.

data (f :*: g) r infixr 7 Source

Structure type for fields of a constructor.

Constructors

(f r) :*: (g r) infixr 7 

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) 
(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) 
(Show f, Show g) => Show ((:*:) f g) 
type CoAlg ((:*:) f g) s = (CoAlg f s, CoAlg g s)

For a produt, the coalgebra is a pair of the two arms.

type Alg ((:*:) (S s (K a)) g) r = a -> Alg g r 
type Alg ((:*:) I g) r = r -> Alg g r

For a product where the left hand side is an identity, we take the recursive result as an additional argument.

type Alg ((:*:) (K a) g) r = a -> Alg g r

For a product where the left hand side is a constant, we take the value as an additional argument.

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) 
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) 
type CoAlg (C c f) s = CoAlg f s

Constructors are ignored.

type Alg (C c f) r = Alg f r

Constructors are ignored.

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) 
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)) 
(Selector s, Show f) => Show (S s f) 
type CoAlg (S r f) s = CoAlg f s

Selectors are ignored.

type Alg (S s f) r = Alg f r

Selectors are ignored.

type Alg ((:*:) (S s (K a)) g) r = a -> Alg g r 

class Constructor c where Source

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.

Minimal complete definition

conName

Methods

conName :: t c (f :: * -> *) r -> String Source

conFixity :: t c (f :: * -> *) r -> Fixity Source

conIsRecord :: t c (f :: * -> *) r -> Bool Source

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 where Source

Methods

selName :: t s (f :: * -> *) r -> String Source

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 where Source

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 a Source

to :: PF a a -> a Source

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.