generic-deriving-1.0.1: Generic programming library for generalized deriving.

Generics.Deriving.Base

Contents

Synopsis

Generic representation types

data V1 p Source

Void: used for datatypes without constructors

data U1 p Source

Unit: used for constructors without arguments

Constructors

U1 

Instances

GEq' U1 
Enum' U1 
GFunctor' U1 
GShow' U1 
Uniplate' U1 a 

newtype Par1 p Source

Used for marking occurrences of the parameter

Constructors

Par1 

Fields

unPar1 :: p
 

Instances

GFunctor' Par1 

newtype Rec1 f p Source

Recursive calls of kind * -> *

Constructors

Rec1 

Fields

unRec1 :: f p
 

Instances

GFunctor f => GFunctor' (Rec1 f) 

newtype K1 i c p Source

Constants, additional parameters and recursion of kind *

Constructors

K1 

Fields

unK1 :: c
 

Instances

GEq c => GEq' (K1 i c) 
GEnum c => Enum' (K1 i c) 
GFunctor' (K1 i c) 
GShow c => GShow' (K1 i c) 
Uniplate' (K1 i a) b 
Uniplate' (K1 i a) a 

newtype M1 i c f p Source

Meta-information (constructor names, etc.)

Constructors

M1 

Fields

unM1 :: f p
 

Instances

GEq' a => GEq' (M1 i c a) 
Enum' f => Enum' (M1 i c f) 
GFunctor' f => GFunctor' (M1 i c f) 
(Selector s, GShow' a) => GShow' (M1 S s a) 
(GShow' a, Constructor c) => GShow' (M1 C c a) 
GShow' a => GShow' (M1 D d a) 
Uniplate' f b => Uniplate' (M1 i c f) b 

data (f :+: g) p Source

Sums: encode choice between constructors

Constructors

L1 

Fields

unL1 :: f p
 
R1 

Fields

unR1 :: g p
 

Instances

(GEq' a, GEq' b) => GEq' (:+: a b) 
(Enum' f, Enum' g) => Enum' (:+: f g) 
(GFunctor' f, GFunctor' g) => GFunctor' (:+: f g) 
(GShow' a, GShow' b) => GShow' (:+: a b) 
(Uniplate' f b, Uniplate' g b) => Uniplate' (:+: f g) b 

data (f :*: g) p Source

Products: encode multiple arguments to constructors

Constructors

(f p) :*: (g p) 

Instances

(GEq' a, GEq' b) => GEq' (:*: a b) 
(Enum' f, Enum' g) => Enum' (:*: f g) 
(GFunctor' f, GFunctor' g) => GFunctor' (:*: f g) 
(GShow' a, GShow' b) => GShow' (:*: a b) 
(Uniplate' f b, Uniplate' g b) => Uniplate' (:*: f g) b 

newtype (f :.: g) p Source

Composition of functors

Constructors

Comp1 

Fields

unComp1 :: f (g p)
 

Instances

(GFunctor f, GFunctor' g) => GFunctor' (:.: f g) 

Synonyms for convenience

type Rec0 = K1 RSource

Type synonym for encoding recursion (of kind *)

type Par0 = K1 PSource

Type synonym for encoding parameters (other than the last)

data R Source

Tag for K1: recursion (of kind *)

data P Source

Tag for K1: parameters (other than the last)

type D1 = M1 DSource

Type synonym for encoding meta-information for datatypes

type C1 = M1 CSource

Type synonym for encoding meta-information for constructors

type S1 = M1 SSource

Type synonym for encoding meta-information for record selectors

data D Source

Tag for M1: datatype

Instances

GShow' a => GShow' (M1 D d a) 

data C Source

Tag for M1: constructor

Instances

(GShow' a, Constructor c) => GShow' (M1 C c a) 

data S Source

Tag for M1: record selector

Instances

(Selector s, GShow' a) => GShow' (M1 S s a) 

Meta-information

class Datatype d whereSource

Class for datatypes that represent datatypes

Methods

datatypeName :: t d (f :: * -> *) a -> StringSource

The name of the datatype, fully qualified

moduleName :: t d (f :: * -> *) a -> StringSource

Instances

Datatype List__ 
Datatype Maybe_ 

class Constructor c whereSource

Class for datatypes that represent data constructors

Methods

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

The name of the constructor

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

The fixity of the constructor

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

Marks if this constructor is a record

Instances

Constructor Cons__ 
Constructor Nil__ 
Constructor Just_ 
Constructor Nothing_ 

class Selector s whereSource

Class for datatypes that represent records

Methods

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

The name of the selector

Instances

data NoSelector Source

Used for constructor fields without a name

Instances

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 

data Associativity Source

Datatype to represent the associativy of a constructor

data Arity Source

Datatype to represent the arity of a tuple.

Constructors

NoArity 
Arity Int 

prec :: Fixity -> IntSource

Get the precedence of a fixity value.

Generic type classes

class Generic a whereSource

Representable types of kind *

Associated Types

type Rep a :: * -> *Source

Methods

from :: a -> Rep a xSource

Convert from the datatype to its representation

to :: Rep a x -> aSource

Convert from the representation to the datatype

class Generic1 f whereSource

Representable types of kind * -> *

Associated Types

type Rep1 f :: * -> *Source

Methods

from1 :: f a -> Rep1 f aSource

Convert from the datatype to its representation

to1 :: Rep1 f a -> f aSource

Convert from the representation to the datatype

Instances