base-compat-0.7.1: A compatibility layer for base

Safe HaskellSafe-Inferred
LanguageHaskell98

GHC.Generics.Compat

Contents

Synopsis

Generic representation types

data U1 p :: * -> *

Unit: used for constructors without arguments

Constructors

U1 

Instances

Eq (U1 p) 
Ord (U1 p) 
Read (U1 p) 
Show (U1 p) 
Generic (U1 p) 
type Rep (U1 p) = D1 D1U1 (C1 C1_0U1 U1) 

newtype Par1 p :: * -> *

Used for marking occurrences of the parameter

Constructors

Par1 

Fields

unPar1 :: p
 

Instances

Eq p => Eq (Par1 p) 
Ord p => Ord (Par1 p) 
Read p => Read (Par1 p) 
Show p => Show (Par1 p) 
Generic (Par1 p) 
type Rep (Par1 p) = D1 D1Par1 (C1 C1_0Par1 (S1 S1_0_0Par1 (Rec0 p))) 

newtype Rec1 f p :: (* -> *) -> * -> *

Recursive calls of kind * -> *

Constructors

Rec1 

Fields

unRec1 :: f p
 

Instances

Eq (f p) => Eq (Rec1 f p) 
Ord (f p) => Ord (Rec1 f p) 
Read (f p) => Read (Rec1 f p) 
Show (f p) => Show (Rec1 f p) 
Generic (Rec1 f p) 
type Rep (Rec1 f p) = D1 D1Rec1 (C1 C1_0Rec1 (S1 S1_0_0Rec1 (Rec0 (f p)))) 

newtype K1 i c p :: * -> * -> * -> *

Constants, additional parameters and recursion of kind *

Constructors

K1 

Fields

unK1 :: c
 

Instances

Eq c => Eq (K1 i c p) 
Ord c => Ord (K1 i c p) 
Read c => Read (K1 i c p) 
Show c => Show (K1 i c p) 
Generic (K1 i c p) 
type Rep (K1 i c p) = D1 D1K1 (C1 C1_0K1 (S1 S1_0_0K1 (Rec0 c))) 

newtype M1 i c f p :: * -> * -> (* -> *) -> * -> *

Meta-information (constructor names, etc.)

Constructors

M1 

Fields

unM1 :: f p
 

Instances

Eq (f p) => Eq (M1 i c f p) 
Ord (f p) => Ord (M1 i c f p) 
Read (f p) => Read (M1 i c f p) 
Show (f p) => Show (M1 i c f p) 
Generic (M1 i c f p) 
type Rep (M1 i c f p) = D1 D1M1 (C1 C1_0M1 (S1 S1_0_0M1 (Rec0 (f p)))) 

data (f :+: g) p :: (* -> *) -> (* -> *) -> * -> * infixr 5

Sums: encode choice between constructors

Constructors

L1 (f p) 
R1 (g p) 

Instances

(Eq (f p), Eq (g p)) => Eq ((:+:) f g p) 
(Ord (f p), Ord (g p)) => Ord ((:+:) f g p) 
(Read (f p), Read (g p)) => Read ((:+:) f g p) 
(Show (f p), Show (g p)) => Show ((:+:) f g p) 
Generic ((:+:) f g p) 
type Rep ((:+:) f g p) = D1 D1:+: ((:+:) (C1 C1_0:+: (S1 NoSelector (Rec0 (f p)))) (C1 C1_1:+: (S1 NoSelector (Rec0 (g p))))) 

data (f :*: g) p :: (* -> *) -> (* -> *) -> * -> * infixr 6

Products: encode multiple arguments to constructors

Constructors

(f p) :*: (g p) infixr 6 

Instances

(Eq (f p), Eq (g p)) => Eq ((:*:) f g p) 
(Ord (f p), Ord (g p)) => Ord ((:*:) f g p) 
(Read (f p), Read (g p)) => Read ((:*:) f g p) 
(Show (f p), Show (g p)) => Show ((:*:) f g p) 
Generic ((:*:) f g p) 
type Rep ((:*:) f g p) = D1 D1:*: (C1 C1_0:*: ((:*:) (S1 NoSelector (Rec0 (f p))) (S1 NoSelector (Rec0 (g p))))) 

newtype (f :.: g) p :: (* -> *) -> (* -> *) -> * -> * infixr 7

Composition of functors

Constructors

Comp1 

Fields

unComp1 :: f (g p)
 

Instances

Eq (f (g p)) => Eq ((:.:) f g p) 
Ord (f (g p)) => Ord ((:.:) f g p) 
Read (f (g p)) => Read ((:.:) f g p) 
Show (f (g p)) => Show ((:.:) f g p) 
Generic ((:.:) f g p) 
type Rep ((:.:) f g p) = D1 D1:.: (C1 C1_0:.: (S1 S1_0_0:.: (Rec0 (f (g p))))) 

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 a :: * -> *

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 All 
Generic Any 
Generic Arity 
Generic Fixity 
Generic Associativity 
Generic [a] 
Generic (U1 p) 
Generic (Par1 p) 
Generic (ZipList a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Maybe a) 
Generic (Either a b) 
Generic (Rec1 f p) 
Generic (a, b) 
Generic (Const a b) 
Generic (WrappedMonad m a) 
Generic (Proxy * t) 
Generic (K1 i c p) 
Generic ((:+:) f g p) 
Generic ((:*:) f g p) 
Generic ((:.:) f g p) 
Generic (a, b, c) 
Generic (WrappedArrow a b c) 
Generic (Alt k f a) 
Generic (M1 i c f p) 
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 * -> *. This class is derivable in GHC with the DeriveGeneric flag on.

Associated Types

type Rep1 f :: * -> *

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