instant-generics-0.4.1: Generic programming library with a sum of products view

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

Generics.Instant.Base

Description

This module defines the basic representation types and the conversion functions to and from. A typical instance for a user-defined datatype would be:

 -- Example datatype
 data Exp = Const Int | Plus Exp Exp

 -- Auxiliary datatypes for constructor representations
 data Const
 data Plus
 
 instance Constructor Const where conName _ = "Const"
 instance Constructor Plus  where conName _ = "Plus"
 
 -- Representable instance
 instance Representable Exp where
   type Rep Exp = C Const (Var Int) :+: C Plus (Rec Exp :*: Rec Exp)
 
   from (Const n)   = L (C (Var n))
   from (Plus e e') = R (C (Rec e :*: Rec e'))
 
   to (L (C (Var n)))            = Const n
   to (R (C (Rec e :*: Rec e'))) = Plus e e'

Synopsis

Documentation

data Z Source

data U Source

Constructors

U 

Instances

data a :+: b infixr 5 Source

Constructors

L a 
R b 

Instances

(Read a, Read b) => Read ((:+:) a b) 
(Show a, Show b) => Show ((:+:) a b) 
(Representable a, Representable b) => Representable ((:+:) a b) 
(HasRec a, HasRec b) => HasRec ((:+:) a b) 
(HasRec a, Empty a, Empty b) => Empty ((:+:) a b) 
(GEnum f, GEnum g) => GEnum ((:+:) f g) 
type Rep ((:+:) a b) = (:+:) a b 

data a :*: b infixr 6 Source

Constructors

a :*: b infixr 6 

Instances

(Read a, Read b) => Read ((:*:) a b) 
(Show a, Show b) => Show ((:*:) a b) 
(Representable a, Representable b) => Representable ((:*:) a b) 
(HasRec a, HasRec b) => HasRec ((:*:) a b) 
(Empty a, Empty b) => Empty ((:*:) a b) 
(GEnum f, GEnum g) => GEnum ((:*:) f g) 
type Rep ((:*:) a b) = (:*:) a b 

data CEq c p q a where Source

Constructors

C :: a -> CEq c p p a 

Instances

Read a => Read (CEq k k c p p a) 
Show a => Show (CEq k k c p q a) 
Representable a => Representable (CEq * * c p q a) 
HasRec a => HasRec (CEq k k c p q a) 
Empty a => Empty (CEq k k c p p a) 
GEnum (CEq k k c p q a) 
GEnum a => GEnum (CEq k k c p p a) 
type Rep (CEq * * c p q a) = CEq * * c p q a 

type C c a = CEq c () () a Source

data Var a Source

Constructors

Var a 

Instances

Read a => Read (Var a) 
Show a => Show (Var a) 
Representable a => Representable (Var a) 
HasRec (Var a) 
Empty a => Empty (Var a) 
GEnum a => GEnum (Var a) 
type Rep (Var a) = Var a 

data Rec a Source

Constructors

Rec a 

Instances

Read a => Read (Rec a) 
Show a => Show (Rec a) 
Representable a => Representable (Rec a) 
HasRec (Rec a) 
Empty a => Empty (Rec a) 
GEnum a => GEnum (Rec a) 
type Rep (Rec a) = Rec a 

class Constructor c where Source

Class for datatypes that represent data constructors. For non-symbolic constructors, only conName has to be defined.

Minimal complete definition

conName

Methods

conName :: t c p q a -> String Source

conFixity :: t c p q a -> Fixity Source

conIsRecord :: t c p q a -> 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 

data Associativity Source

Datatype to represent the associativy of a constructor.

type family X c n a :: k2 Source

data Nat Source

Constructors

Ze 
Su Nat