compdata-0.8.1.3: Compositional Data Types

Copyright(c) 2010-2011 Patrick Bahr
LicenseBSD3
MaintainerPatrick Bahr <paba@diku.dk>
Stabilityexperimental
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell98

Data.Comp.Multi.Derive

Contents

Description

This module contains functionality for automatically deriving boilerplate code using Template Haskell. Examples include instances of HFunctor, HFoldable, and HTraversable.

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 higher-order signatures, i.e. signatures for generalised compositional data types.

HShowF

class ShowHF f where Source

Signature printing. An instance ShowHF f gives rise to an instance KShow (HTerm f).

Minimal complete definition

Nothing

Instances

(ShowHF f, HFunctor f) => ShowHF (Cxt h f) 
(ShowHF f, Show p) => ShowHF ((:&:) * f p) 
(ShowHF f, ShowHF g) => ShowHF ((:+:) * f g) 

class KShow a where Source

Methods

kshow :: a i -> K String i Source

Instances

KShow (K String) 
KShow (K ()) 
(ShowHF f, HFunctor f, KShow a) => KShow (Cxt h f a) 

makeShowHF :: Name -> Q [Dec] Source

Derive an instance of ShowHF for a type constructor of any higher-order kind taking at least two arguments.

EqHF

class EqHF f where Source

Signature equality. An instance EqHF f gives rise to an instance KEq (HTerm f).

Methods

eqHF :: KEq g => f g i -> f g j -> Bool Source

Instances

EqHF f => EqHF (Cxt h f) 
(EqHF f, EqHF g) => EqHF ((:+:) * f g)

EqF is propagated through sums.

class KEq f where Source

Methods

keq :: f i -> f j -> Bool Source

Instances

Eq a => KEq (K a) 
KEq (Numbered a) 
(EqHF f, KEq a) => KEq (Cxt h f a) 

makeEqHF :: Name -> Q [Dec] Source

Derive an instance of EqHF for a type constructor of any higher-order kind taking at least two arguments.

OrdHF

class EqHF f => OrdHF f where Source

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

Methods

compareHF :: KOrd a => f a i -> f a j -> Ordering Source

Instances

(HFunctor f, OrdHF f) => OrdHF (Cxt h f)

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

(OrdHF f, OrdHF g) => OrdHF ((:+:) * f g)

OrdHF is propagated through sums.

makeOrdHF :: Name -> Q [Dec] Source

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

HFunctor

class HFunctor h Source

This class represents higher-order functors (Johann, Ghani, POPL '08) which are endofunctors on the category of endofunctors.

Minimal complete definition

hfmap

Instances

HFunctor f => HFunctor (Cxt h f) 
HFunctor f => HFunctor ((:&:) * f a) 
(HFunctor f, HFunctor g) => HFunctor ((:+:) * f g) 

makeHFunctor :: Name -> Q [Dec] Source

Derive an instance of HFunctor for a type constructor of any higher-order kind taking at least two arguments.

HFoldable

class HFunctor h => HFoldable h Source

Higher-order functors that can be folded.

Minimal complete definition: hfoldMap or hfoldr.

Instances

HFoldable f => HFoldable (Cxt h f) 
HFoldable f => HFoldable ((:&:) * f a) 
(HFoldable f, HFoldable g) => HFoldable ((:+:) * f g) 

makeHFoldable :: Name -> Q [Dec] Source

Derive an instance of HFoldable for a type constructor of any higher-order kind taking at least two arguments.

HTraversable

class HFoldable t => HTraversable t Source

Minimal complete definition

hmapM, htraverse

makeHTraversable :: Name -> Q [Dec] Source

Derive an instance of HTraversable for a type constructor of any higher-order kind taking at least two arguments.

Smart Constructors

smartConstructors :: Name -> Q [Dec] Source

Derive smart constructors for a type constructor of any higher-order 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 higher-order functor, lift it to sums of higher-order. Example: class HShowF f where ... is lifted as instance (HShowF f, HShowF g) => HShowF (f :+: g) where ... .