compdata-param-0.8: Parametric Compositional Data Types

Copyright(c) 2011 Patrick Bahr, Tom Hvitved
LicenseBSD3
MaintainerTom Hvitved <hvitved@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell98

Data.Comp.Param.Derive

Contents

Description

This module contains functionality for automatically deriving boilerplate code using Template Haskell. Examples include instances of Difunctor, Difoldable, and Ditraversable.

Synopsis

Documentation

derive :: [Name -> Q [Dec]] -> [Name] -> Q [Dec]

Helper function for generating a list of instances for a list of named signatures. For example, in order to derive instances Functor and ShowF for a signature Exp, use derive as follows (requires Template Haskell):

$(derive [makeFunctor, makeShowF] [''Exp])

Derive boilerplate instances for parametric signatures, i.e. signatures for parametric compositional data types.

EqD

class EqD f where Source

Signature equality. An instance EqD f gives rise to an instance Eq (Term f). The equality test is performed inside the FreshM monad for generating fresh identifiers.

Methods

eqD :: PEq a => f Name a -> f Name a -> FreshM Bool Source

Instances

(EqD f, EqD g) => EqD ((:+:) f g)

EqD is propagated through sums.

EqD f => EqD (Cxt h f)

From an EqD difunctor an Eq instance of the corresponding term type can be derived.

makeEqD :: Name -> Q [Dec] Source

Derive an instance of EqD for a type constructor of any parametric kind taking at least two arguments.

OrdD

class EqD f => OrdD f where Source

Signature ordering. An instance OrdD f gives rise to an instance Ord (Term f).

Methods

compareD :: POrd a => f Name a -> f Name a -> FreshM Ordering Source

Instances

(OrdD f, OrdD g) => OrdD ((:+:) f g)

OrdD is propagated through sums.

OrdD f => OrdD (Cxt h f)

From an OrdD difunctor an Ord instance of the corresponding term type can be derived.

makeOrdD :: Name -> Q [Dec] Source

Derive an instance of OrdD for a type constructor of any parametric kind taking at least two arguments.

ShowD

class ShowD f where Source

Signature printing. An instance ShowD f gives rise to an instance Show (Term f).

Instances

(ShowD f, Show p) => ShowD ((:&:) f p) 
(ShowD f, ShowD g) => ShowD ((:+:) f g) 
(Difunctor f, ShowD f) => ShowD (Cxt h f)

From an ShowD difunctor an ShowD instance of the corresponding term type can be derived.

makeShowD :: Name -> Q [Dec] Source

Derive an instance of ShowD for a type constructor of any parametric kind taking at least two arguments.

Difunctor

class Difunctor f Source

This class represents difunctors, i.e. binary type constructors that are contravariant in the first argument and covariant in the second argument.

Minimal complete definition

dimap

Instances

Difunctor (->)

The canonical example of a difunctor.

Difunctor f => Difunctor ((:&:) f p) 
(Difunctor f, Difunctor g) => Difunctor ((:+:) f g) 

makeDifunctor :: Name -> Q [Dec] Source

Derive an instance of Difunctor for a type constructor of any parametric kind taking at least two arguments.

Ditraversable

class Difunctor f => Ditraversable f Source

Difunctors representing data structures that can be traversed from left to right.

makeDitraversable :: Name -> Q [Dec] Source

Derive an instance of Traversable for a type constructor of any first-order kind taking at least one argument.

Smart Constructors

smartConstructors :: Name -> Q [Dec] Source

Derive smart constructors for a difunctor. The smart constructors are similar to the ordinary constructors, but a 'inject . dimap Var id' is automatically inserted.

Smart Constructors w/ Annotations

smartAConstructors :: Name -> Q [Dec] Source

Derive smart constructors with annotations for a difunctor. The smart constructors are similar to the ordinary constructors, but a 'injectA . dimap Var id' is automatically inserted.

Lifting to Sums

liftSum :: Name -> Q [Dec] Source

Given the name of a type class, where the first parameter is a difunctor, lift it to sums of difunctors. Example: class ShowD f where ... is lifted as instance (ShowD f, ShowD g) => ShowD (f :+: g) where ... .