base-4.6.0.0: Basic libraries

Safe HaskellTrustworthy

GHC.Generics

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 

newtype Par1 p Source

Used for marking occurrences of the parameter

Constructors

Par1 

Fields

unPar1 :: p
 

newtype Rec1 f p Source

Recursive calls of kind * -> *

Constructors

Rec1 

Fields

unRec1 :: f p
 

newtype K1 i c p Source

Constants, additional parameters and recursion of kind *

Constructors

K1 

Fields

unK1 :: c
 

newtype M1 i c f p Source

Meta-information (constructor names, etc.)

Constructors

M1 

Fields

unM1 :: f p
 

data (f :+: g) p Source

Sums: encode choice between constructors

Constructors

L1 (f p) 
R1 (g p) 

data (f :*: g) p Source

Products: encode multiple arguments to constructors

Constructors

(f p) :*: (g p) 

newtype (f :.: g) p Source

Composition of functors

Constructors

Comp1 

Fields

unComp1 :: f (g p)
 

Synonyms for convenience

type Rec0 = K1 RSource

Type synonym for encoding recursion (of kind *)

type Par0 = K1 PSource

Deprecated: Par0 is no longer used; use Rec0 instead

Type synonym for encoding parameters (other than the last)

data R Source

Tag for K1: recursion (of kind *)

data P Source

Deprecated: P is no longer used; use R instead

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

data C Source

Tag for M1: constructor

data S Source

Tag for M1: record selector

Meta-information

class Datatype d whereSource

Class for datatypes that represent datatypes

Methods

datatypeName :: t d (f :: * -> *) a -> [Char]Source

The name of the datatype (unqualified)

moduleName :: t d (f :: * -> *) a -> [Char]Source

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

Instances

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

class Constructor c whereSource

Class for datatypes that represent data constructors

Methods

conName :: t c (f :: * -> *) a -> [Char]Source

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 C1_0(,,,,,,) 
Constructor C1_0(,,,,,) 
Constructor C1_0(,,,,) 
Constructor C1_0(,,,) 
Constructor C1_0(,,) 
Constructor C1_0(,) 
Constructor C1_0Either 
Constructor C1_1Either 
Constructor C1_0Maybe 
Constructor C1_1Maybe 
Constructor C1_0[] 
Constructor C1_1[] 
Constructor C1_0() 
Constructor C1_0Ordering 
Constructor C1_1Ordering 
Constructor C1_2Ordering 
Constructor C1_0Bool 
Constructor C1_1Bool 
Constructor C_Char 
Constructor C_Double 
Constructor C_Float 
Constructor C_Int 

class Selector s whereSource

Class for datatypes that represent records

Methods

selName :: t s (f :: * -> *) a -> [Char]Source

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 associativity 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 *. This class is derivable in GHC with the DeriveGeneric flag on.

Associated Types

type Rep a :: * -> *Source

Generic representation type

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

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 whereSource

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

Associated Types

type Rep1 f :: * -> *Source

Generic representation type

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

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)