generics-eot-0.1: A library for generic programming that aims to be easy to understand

Safe HaskellNone
LanguageHaskell2010

Generics.Eot

Contents

Description

generics-eot tries to be a library for datatype generic programming that is easy to understand. "eot" stands for "eithers of tuples".

A tutorial on how to use generics-eot can be found here: Generics.Eot.Tutorial.

Synopsis

Documentation

class HasEot a where Source

An instance (HasEot a) allows us to

  • convert values of an arbitrary algebraic datatype a to and from a generic representation (Eot a) (see toEot and fromEot).
  • extract meta information about the type a (see datatype).

Once an algebraic datatype has an instance for Generic it automatically gets one for HasEot.

Associated Types

type Eot a :: * Source

Eot is a type level function that maps arbitrary ADTs to isomorphic generic representations. Here's an example:

data Foo = A Int Bool | B String

would be mapped to:

Either (Int, (Bool, ())) (Either (String, ()) Void)

These representations follow these rules:

  • The choice between constructors is mapped to right-nested Eithers.
  • There's always a so-called end-marker Void. It's an invalid choice (and Void is uninhabited to make sure you don't accidentally create such a value). So e.g. data Foo = A would be mapped to Either () Void, and a type with no constructors is mapped to Void.
  • The fields of one constructor are mapped to right-nested tuples.
  • Again there's always an end-marker, this time of type (). A constructor with three fields a, b, c is mapped to (a, (b, (c, ()))), one field a is mapped to (a, ()), and no fields are mapped to () (just the end-marker).

These rules (and the end-markers) are necessary to make sure generic functions know exactly which parts of the generic representation are field types and which parts belong to the generic skeleton.

Methods

toEot :: a -> Eot a Source

Convert a value of type a to its generic representation.

fromEot :: Eot a -> a Source

Convert a value in a generic representation to a (inverse of toEot).

datatype :: Proxy a -> Datatype Source

Extract meta information about the ADT.

Instances

(Generic a, ImpliedByGeneric a c f) => HasEot a Source 

Meta Information

data Datatype Source

Type for meta information about ADTs.

Constructors

Datatype 

Fields

datatypeName :: String

unqualified name of the type

constructors :: [Constructor]
 

data Fields Source

Type that represents meta information about fields of one constructor.

Constructors

Selectors [String]

Record constructor, containing the list of the selector names.

NoSelectors Int

Constructor with fields, but without selector names. The argument gives the number of fields.

NoFields

Constructor without fields.

Void

Useful Re-exports

class Generic a

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

Minimal complete definition

from, to

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 Void 
Generic C 
Generic NoSelectors 
Generic Person 
Generic B 
Generic A 
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) 

data Proxy t :: k -> *

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Monad (Proxy *) 
Functor (Proxy *) 
Applicative (Proxy *) 
Foldable (Proxy *) 
Bounded (Proxy k s) 
Enum (Proxy k s) 
Eq (Proxy k s) 
Ord (Proxy k s) 
Read (Proxy k s) 
Show (Proxy k s) 
Ix (Proxy k s) 
Generic (Proxy * t) 
Monoid (Proxy k s) 
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1)