generics-sop-0.1.1.2: Generic Programming using True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Universe

Description

Codes and interpretations

Synopsis

Documentation

type Rep a = SOP I (Code a) Source

The (generic) representation of a datatype.

A datatype is isomorphic to the sum-of-products of its code. The isomorphism is witnessed by from and to from the Generic class.

class (SingI (Code a), All SingI (Code a)) => Generic a where Source

The class of representable datatypes.

The SOP approach to generic programming is based on viewing datatypes as a representation (Rep) built from the sum of products of its components. The components of are datatype are specified using the Code type family.

The isomorphism between the original Haskell datatype and its representation is witnessed by the methods of this class, from and to. So for instances of this class, the following laws should (in general) hold:

to . from === id :: a -> a
from . to === id :: Rep a -> Rep a

You typically don't define instances of this class by hand, but rather derive the class instance automatically.

Option 1: Derive via the built-in GHC-generics. For this, you need to use the DeriveGeneric extension to first derive an instance of the Generic class from module GHC.Generics. With this, you can then give an empty instance for Generic, and the default definitions will just work. The pattern looks as follows:

import qualified GHC.Generics as GHC
import Generics.SOP

...

data T = ... deriving (GHC.Generic, ...)

instance Generic T -- empty
instance HasDatatypeInfo T -- empty, if you want/need metadata

Option 2: Derive via Template Haskell. For this, you need to enable the TemplateHaskell extension. You can then use deriveGeneric from module Generics.SOP.TH to have the instance generated for you. The pattern looks as follows:

import Generics.SOP
import Generics.SOP.TH

...

data T = ...

deriveGeneric ''T -- derives HasDatatypeInfo as well

Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.

Non-standard instances: It is possible to give Generic instances manually that deviate from the standard scheme, as long as at least

to . from === id :: a -> a

still holds.

Minimal complete definition

Nothing

Associated Types

type Code a :: [[*]] Source

The code of a datatype.

This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).

Example: The datatype

data Tree = Leaf Int | Node Tree Tree

is supposed to have the following code:

type instance Code (Tree a) =
  '[ '[ Int ]
   , '[ Tree, Tree ]
   ]

Methods

from :: a -> Rep a Source

Converts from a value to its structural representation.

to :: Rep a -> a Source

Converts from a structural representation back to the original value.

Instances

Generic Bool 
Generic Ordering 
Generic () 
Generic FormatAdjustment 
Generic FormatSign 
Generic FieldFormat 
Generic FormatParse 
Generic DataRep 
Generic ConstrRep 
Generic Fixity 
Generic Version 
Generic IOMode 
Generic PatternMatchFail 
Generic RecSelError 
Generic RecConError 
Generic RecUpdError 
Generic NoMethodError 
Generic NonTermination 
Generic NestedAtomically 
Generic Errno 
Generic BlockedIndefinitelyOnMVar 
Generic BlockedIndefinitelyOnSTM 
Generic Deadlock 
Generic AssertionFailed 
Generic AsyncException 
Generic ArrayException 
Generic ExitCode 
Generic BufferMode 
Generic Newline 
Generic NewlineMode 
Generic SeekMode 
Generic GeneralCategory 
Generic CChar 
Generic CSChar 
Generic CUChar 
Generic CShort 
Generic CUShort 
Generic CInt 
Generic CUInt 
Generic CLong 
Generic CULong 
Generic CLLong 
Generic CULLong 
Generic CFloat 
Generic CDouble 
Generic CPtrdiff 
Generic CSize 
Generic CWchar 
Generic CSigAtomic 
Generic CClock 
Generic CTime 
Generic CUSeconds 
Generic CSUSeconds 
Generic CIntPtr 
Generic CUIntPtr 
Generic CIntMax 
Generic CUIntMax 
Generic MaskingState 
Generic IOException 
Generic ErrorCall 
Generic ArithException 
Generic All 
Generic Any 
Generic Lexeme 
Generic Number 
Generic [a] 
Generic (ArgOrder a) 
Generic (OptDescr a) 
Generic (ArgDescr a) 
Generic (Fixed a) 
Generic (Complex a) 
Generic (Dual a) 
Generic (Endo a) 
Generic (Sum a) 
Generic (Product a) 
Generic (First a) 
Generic (Last a) 
Generic (Down a) 
Generic (Maybe a) 
Generic (I a) 
Generic (Either a b) 
Generic (a, b) 
Generic (Proxy * t) 
Typeable (* -> Constraint) Generic 
Generic (a, b, c) 
Generic (K * a b) 
Generic (a, b, c, d) 
Generic (a, b, c, d, e) 
Generic ((:.:) * * f g p) 
Generic (a, b, c, d, e, f) 
Generic (a, b, c, d, e, f, g) 
Generic (a, b, c, d, e, f, g, h) 
Generic (a, b, c, d, e, f, g, h, i) 
Generic (a, b, c, d, e, f, g, h, i, j) 
Generic (a, b, c, d, e, f, g, h, i, j, k) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29, t30) 
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29, t30, t31) 

class HasDatatypeInfo a where Source

A class of datatypes that have associated metadata.

It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.

You typically don't define instances of this class by hand, but rather derive the class instance automatically. See the documentation of Generic for the options.

Minimal complete definition

Nothing

Instances

HasDatatypeInfo Bool 
HasDatatypeInfo Ordering 
HasDatatypeInfo () 
HasDatatypeInfo FormatAdjustment 
HasDatatypeInfo FormatSign 
HasDatatypeInfo FieldFormat 
HasDatatypeInfo FormatParse 
HasDatatypeInfo DataRep 
HasDatatypeInfo ConstrRep 
HasDatatypeInfo Fixity 
HasDatatypeInfo Version 
HasDatatypeInfo IOMode 
HasDatatypeInfo PatternMatchFail 
HasDatatypeInfo RecSelError 
HasDatatypeInfo RecConError 
HasDatatypeInfo RecUpdError 
HasDatatypeInfo NoMethodError 
HasDatatypeInfo NonTermination 
HasDatatypeInfo NestedAtomically 
HasDatatypeInfo Errno 
HasDatatypeInfo BlockedIndefinitelyOnMVar 
HasDatatypeInfo BlockedIndefinitelyOnSTM 
HasDatatypeInfo Deadlock 
HasDatatypeInfo AssertionFailed 
HasDatatypeInfo AsyncException 
HasDatatypeInfo ArrayException 
HasDatatypeInfo ExitCode 
HasDatatypeInfo BufferMode 
HasDatatypeInfo Newline 
HasDatatypeInfo NewlineMode 
HasDatatypeInfo SeekMode 
HasDatatypeInfo GeneralCategory 
HasDatatypeInfo CChar 
HasDatatypeInfo CSChar 
HasDatatypeInfo CUChar 
HasDatatypeInfo CShort 
HasDatatypeInfo CUShort 
HasDatatypeInfo CInt 
HasDatatypeInfo CUInt 
HasDatatypeInfo CLong 
HasDatatypeInfo CULong 
HasDatatypeInfo CLLong 
HasDatatypeInfo CULLong 
HasDatatypeInfo CFloat 
HasDatatypeInfo CDouble 
HasDatatypeInfo CPtrdiff 
HasDatatypeInfo CSize 
HasDatatypeInfo CWchar 
HasDatatypeInfo CSigAtomic 
HasDatatypeInfo CClock 
HasDatatypeInfo CTime 
HasDatatypeInfo CUSeconds 
HasDatatypeInfo CSUSeconds 
HasDatatypeInfo CIntPtr 
HasDatatypeInfo CUIntPtr 
HasDatatypeInfo CIntMax 
HasDatatypeInfo CUIntMax 
HasDatatypeInfo MaskingState 
HasDatatypeInfo IOException 
HasDatatypeInfo ErrorCall 
HasDatatypeInfo ArithException 
HasDatatypeInfo All 
HasDatatypeInfo Any 
HasDatatypeInfo Lexeme 
HasDatatypeInfo Number 
HasDatatypeInfo [a] 
HasDatatypeInfo (ArgOrder a) 
HasDatatypeInfo (OptDescr a) 
HasDatatypeInfo (ArgDescr a) 
HasDatatypeInfo (Fixed a) 
HasDatatypeInfo (Complex a) 
HasDatatypeInfo (Dual a) 
HasDatatypeInfo (Endo a) 
HasDatatypeInfo (Sum a) 
HasDatatypeInfo (Product a) 
HasDatatypeInfo (First a) 
HasDatatypeInfo (Last a) 
HasDatatypeInfo (Down a) 
HasDatatypeInfo (Maybe a) 
HasDatatypeInfo (I a) 
HasDatatypeInfo (Either a b) 
HasDatatypeInfo (a, b) 
HasDatatypeInfo (Proxy * t) 
Typeable (* -> Constraint) HasDatatypeInfo 
HasDatatypeInfo (a, b, c) 
HasDatatypeInfo (K * a b) 
HasDatatypeInfo (a, b, c, d) 
HasDatatypeInfo (a, b, c, d, e) 
HasDatatypeInfo ((:.:) * * f g p) 
HasDatatypeInfo (a, b, c, d, e, f) 
HasDatatypeInfo (a, b, c, d, e, f, g) 
HasDatatypeInfo (a, b, c, d, e, f, g, h) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29, t30) 
HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t28, t29, t30, t31)