generic-deriving-1.3.0: Generic programming library for generalised deriving.

Safe HaskellSafe-Inferred

Generics.Deriving.Base

Contents

Synopsis

Generic representation types

data V1 p

Void: used for datatypes without constructors

data U1 p

Unit: used for constructors without arguments

Constructors

U1 

Instances

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

newtype Par1 p

Used for marking occurrences of the parameter

Constructors

Par1 

Fields

unPar1 :: p
 

Instances

GFunctor' Par1 
GFoldable' Par1 
GTraversable' Par1 

newtype Rec1 f p

Recursive calls of kind * -> *

Constructors

Rec1 

Fields

unRec1 :: f p
 

Instances

GFunctor f => GFunctor' (Rec1 f) 
GFoldable f => GFoldable' (Rec1 f) 
GTraversable f => GTraversable' (Rec1 f) 

newtype K1 i c p

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) 
GFoldable' (K1 i c) 
GTraversable' (K1 i c) 
Uniplate' (K1 i a) b 
Uniplate' (K1 i a) a 

newtype M1 i c f p

Meta-information (constructor names, etc.)

Constructors

M1 

Fields

unM1 :: f p
 

Instances

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

data (f :+: g) p

Sums: encode choice between constructors

Constructors

L1 (f p) 
R1 (g p) 

Instances

(ConNames f, ConNames g) => ConNames (:+: f g) 
(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) 
(GFoldable' f, GFoldable' g) => GFoldable' (:+: f g) 
(GTraversable' f, GTraversable' g) => GTraversable' (:+: f g) 
(Uniplate' f b, Uniplate' g b) => Uniplate' (:+: f g) b 

data (f :*: g) p

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) 
(GFoldable' f, GFoldable' g) => GFoldable' (:*: f g) 
(GTraversable' f, GTraversable' g) => GTraversable' (:*: f g) 
(Uniplate' f b, Uniplate' g b) => Uniplate' (:*: f g) b 

newtype (f :.: g) p

Composition of functors

Constructors

Comp1 

Fields

unComp1 :: f (g p)
 

Instances

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

Synonyms for convenience

type Rec0 = K1 R

Type synonym for encoding recursion (of kind *)

type Par0 = K1 P

Type synonym for encoding parameters (other than the last)

data R

Tag for K1: recursion (of kind *)

data P

Tag for K1: parameters (other than the last)

type D1 = M1 D

Type synonym for encoding meta-information for datatypes

type C1 = M1 C

Type synonym for encoding meta-information for constructors

type S1 = M1 S

Type synonym for encoding meta-information for record selectors

data D

Tag for M1: datatype

Instances

ConNames f => ConNames (D1 c f) 
GShow' a => GShow' (M1 D d a) 

data C

Tag for M1: constructor

Instances

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

data S

Tag for M1: record selector

Instances

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

Meta-information

class Datatype d where

Class for datatypes that represent datatypes

Methods

datatypeName :: t d f a -> [Char]

The name of the datatype (unqualified)

moduleName :: t d f a -> [Char]

The fully-qualified name of the module where the type is declared

Instances

Datatype D_Int 
Datatype D_Float 
Datatype D_Double 
Datatype D_Char 
Datatype D1[] 
Datatype D1Ordering 
Datatype D1Maybe 
Datatype D1Either 
Datatype D1Bool 
Datatype D1(,,,,,,) 
Datatype D1(,,,,,) 
Datatype D1(,,,,) 
Datatype D1(,,,) 
Datatype D1(,,) 
Datatype D1(,) 
Datatype D1() 

class Constructor c where

Class for datatypes that represent data constructors

Methods

conName :: t c f a -> [Char]

The name of the constructor

conFixity :: t c f a -> Fixity

The fixity of the constructor

conIsRecord :: t c f a -> Bool

Marks if this constructor is a record

Instances

Constructor C_Int 
Constructor C_Float 
Constructor C_Double 
Constructor C_Char 
Constructor C1_1[] 
Constructor C1_0[] 
Constructor C1_2Ordering 
Constructor C1_1Ordering 
Constructor C1_0Ordering 
Constructor C1_1Maybe 
Constructor C1_0Maybe 
Constructor C1_1Either 
Constructor C1_0Either 
Constructor C1_1Bool 
Constructor C1_0Bool 
Constructor C1_0(,,,,,,) 
Constructor C1_0(,,,,,) 
Constructor C1_0(,,,,) 
Constructor C1_0(,,,) 
Constructor C1_0(,,) 
Constructor C1_0(,) 
Constructor C1_0() 

class Selector s where

Class for datatypes that represent records

Methods

selName :: t s f a -> [Char]

The name of the selector

Instances

data NoSelector

Used for constructor fields without a name

Instances

data Fixity

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

Datatype to represent the associativity of a constructor

data Arity

Datatype to represent the arity of a tuple.

Constructors

NoArity 
Arity Int 

prec :: Fixity -> Int

Get the precedence of a fixity value.

Generic type classes

class Generic a where

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Associated Types

type Rep a1 :: * -> *

Generic representation type

Methods

from :: a -> Rep a x

Convert from the datatype to its representation

to :: Rep a x -> a

Convert from the representation to the datatype

Instances

Generic Bool 
Generic Char 
Generic Double 
Generic Float 
Generic Int 
Generic Ordering 
Generic () 
Generic [a] 
Generic (Maybe a) 
Generic (Either a b) 
Generic (a, b) 
Generic (a, b, c) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 

class Generic1 f where

Representable types of kind * -> * (not yet derivable)

Associated Types

type Rep1 f1 :: * -> *

Generic representation type

Methods

from1 :: f a -> Rep1 f a

Convert from the datatype to its representation

to1 :: Rep1 f a -> f a

Convert from the representation to the datatype

Instances

Generic1 [] 
Generic1 Maybe 
Generic1 (Either a) 
Generic1 ((,) a) 
Generic1 ((,,) a b) 
Generic1 ((,,,) a b c) 
Generic1 ((,,,,) a b c d) 
Generic1 ((,,,,,) a b c d e) 
Generic1 ((,,,,,,) a b c d e f)