compdata-0.3: Compositional Data Types

Portabilitynon-portable (GHC Extensions)
Stabilityexperimental
MaintainerTom Hvitved <hvitved@diku.dk>

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]Source

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 whereSource

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 Var a -> f Var a -> FreshM BoolSource

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 whereSource

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

Methods

compareD :: POrd a => f Var a -> f Var a -> FreshM OrderingSource

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 PShow a whereSource

Printing of parametric values.

Methods

pshow :: a -> FreshM StringSource

Instances

Show a => PShow a 
(ShowD f, PShow a) => PShow (Cxt h f Var a) 

class ShowD f whereSource

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

Methods

showD :: PShow a => f Var a -> FreshM StringSource

Instances

(ShowD f, PShow p) => ShowD (:&: f p) 
(ShowD f, ShowD g) => ShowD (:+: f g) 
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.

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, Monad m) => Ditraversable f m a Source

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

Instances

Ditraversable (->) [] Any 
Ditraversable (->) Gen a 
Ditraversable (->) Maybe Any

Functions of the type Any -> Maybe a can be turned into functions of type Maybe (Any -> a). The empty type Any ensures that the function is parametric in the input, and hence the Maybe monad can be pulled out.

Ditraversable (->) Identity a 
Ditraversable (->) (Either e) Any 
Ditraversable (->) m Any => Ditraversable (->) (ListT m) Any 
(Error e, Ditraversable (->) m Any) => Ditraversable (->) (ErrorT e m) Any 
Ditraversable (->) m a => Ditraversable (->) (ReaderT r m) a 
Ditraversable (->) m Any => Ditraversable (->) (StateT s m) Any 
(Monoid w, Ditraversable (->) m Any) => Ditraversable (->) (WriterT w m) Any 
(Monoid w, Ditraversable (->) m Any) => Ditraversable (->) (RWST r w s m) Any 
Ditraversable f m a => Ditraversable (:&: f p) m a 
(Ditraversable f m a, Ditraversable g m a) => Ditraversable (:+: f g) m a 

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 type constructor of any parametric kind taking at least two arguments. The smart constructors are similar to the ordinary constructors, but an inject is automatically inserted.

Smart Constructors w/ Annotations

smartAConstructors :: Name -> Q [Dec]Source

Derive smart constructors with products for a type constructor of any parametric kind taking at least two arguments. The smart constructors are similar to the ordinary constructors, but an injectA 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 ... .

caseD :: (f a b -> c) -> (g a b -> c) -> (f :+: g) a b -> cSource

Utility function to case on a difunctor sum, without exposing the internal representation of sums.