compdata-0.7.0.1: Compositional Data Types

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

Data.Comp.MultiParam.Derive

Contents

Description

This module contains functionality for automatically deriving boilerplate code using Template Haskell. Examples include instances of HDifunctor, ShowHD, and EqHD.

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.

EqHD

class EqHD f whereSource

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

Methods

eqHD :: PEq a => f Name a i -> f Name a j -> FreshM BoolSource

Instances

EqHD f => EqHD (Cxt h f)

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

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

EqHD is propagated through sums.

makeEqHD :: Name -> Q [Dec]Source

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

OrdHD

class EqHD f => OrdHD f whereSource

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

Methods

compareHD :: POrd a => f Name a i -> f Name a j -> FreshM OrderingSource

Instances

OrdHD f => OrdHD (Cxt h f)

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

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

OrdHD is propagated through sums.

makeOrdHD :: Name -> Q [Dec]Source

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

ShowHD

class ShowHD f whereSource

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

Instances

(HDifunctor f, ShowHD f) => ShowHD (Cxt h f)

From an ShowHD higher-order difunctor an ShowHD instance of the corresponding term type can be derived.

(ShowHD f, Show p) => ShowHD (:&: f p) 
(ShowHD f, ShowHD g) => ShowHD (:+: f g) 

makeShowHD :: Name -> Q [Dec]Source

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

HDifunctor

class HDifunctor f Source

This class represents higher-order difunctors.

Instances

makeHDifunctor :: Name -> Q [Dec]Source

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

Smart Constructors

smartConstructors :: Name -> Q [Dec]Source

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

Smart Constructors w/ Annotations

smartAConstructors :: Name -> Q [Dec]Source

Derive smart constructors with annotations for a higher-order difunctor. The smart constructors are similar to the ordinary constructors, but a 'injectA . hdimap 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 higher-order difunctor, lift it to sums of higher-order difunctors. Example: class ShowHD f where ... is lifted as instance (ShowHD f, ShowHD g) => ShowHD (f :+: g) where ... .