compdata-param-0.9.2: 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.Term

Description

This module defines the central notion of parametrised terms and their generalisation to parametrised contexts.

Synopsis

Documentation

data Cxt :: * -> (* -> * -> *) -> * -> * -> * where Source #

This data type represents contexts over a signature. Contexts are terms containing zero or more holes, and zero or more parameters. The first parameter is a phantom type indicating whether the context has holes. The second paramater is the signature of the context, in the form of a Data.Comp.Param.Difunctor. The third parameter is the type of parameters, and the fourth parameter is the type of holes.

Constructors

In :: f a (Cxt h f a b) -> Cxt h f a b 
Hole :: b -> Cxt Hole f a b 
Var :: a -> Cxt h f a b 
Instances
(Difunctor f, ShowD f) => ShowD (Cxt h f) Source #

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

Instance details

Defined in Data.Comp.Param.Show

EqD f => EqD (Cxt h f) Source #

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

Instance details

Defined in Data.Comp.Param.Equality

Methods

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

OrdD f => OrdD (Cxt h f) Source #

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

Instance details

Defined in Data.Comp.Param.Ordering

Methods

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

(EqD f, PEq a) => PEq (Cxt h f Name a) Source # 
Instance details

Defined in Data.Comp.Param.Equality

Methods

peq :: Cxt h f Name a -> Cxt h f Name a -> FreshM Bool Source #

(OrdD f, POrd a) => POrd (Cxt h f Name a) Source # 
Instance details

Defined in Data.Comp.Param.Ordering

Methods

pcompare :: Cxt h f Name a -> Cxt h f Name a -> FreshM Ordering Source #

data Hole Source #

Phantom type used to define Context.

data NoHole Source #

Phantom type used to define Term.

newtype Term f Source #

A term is a context with no holes, where all occurrences of the contravariant parameter is fully parametric.

Constructors

Term 

Fields

Instances
(Difunctor f, EqD f) => Eq (Term f) #

Equality on terms.

Instance details

Defined in Data.Comp.Param.Equality

Methods

(==) :: Term f -> Term f -> Bool #

(/=) :: Term f -> Term f -> Bool #

(Difunctor f, OrdD f) => Ord (Term f) #

Ordering of terms.

Instance details

Defined in Data.Comp.Param.Ordering

Methods

compare :: Term f -> Term f -> Ordering #

(<) :: Term f -> Term f -> Bool #

(<=) :: Term f -> Term f -> Bool #

(>) :: Term f -> Term f -> Bool #

(>=) :: Term f -> Term f -> Bool #

max :: Term f -> Term f -> Term f #

min :: Term f -> Term f -> Term f #

(Difunctor f, ShowD f) => Show (Term f) #

Printing of terms.

Instance details

Defined in Data.Comp.Param.Show

Methods

showsPrec :: Int -> Term f -> ShowS #

show :: Term f -> String #

showList :: [Term f] -> ShowS #

type Trm f a = Cxt NoHole f a () Source #

"Preterms"

type Context = Cxt Hole Source #

A context may contain holes.

simpCxt :: Difunctor f => f a b -> Cxt Hole f a b Source #

Convert a difunctorial value into a context.

toCxt :: Difunctor f => Trm f a -> Cxt h f a b Source #

cxtMap :: Difunctor f => (b -> c) -> Context f a b -> Context f a c Source #

This combinator maps a function over a context by applying the function to each hole.

class ParamFunctor m where Source #

Monads for which embedded Trm values, which are parametric at top level, can be made into monadic Term values, i.e. "pushing the parametricity inwards".

Minimal complete definition

termM

Methods

termM :: (forall a. m (Trm f a)) -> m (Term f) Source #

Instances
ParamFunctor [] Source # 
Instance details

Defined in Data.Comp.Param.Term

Methods

termM :: (forall a. [Trm f a]) -> [Term f] Source #

ParamFunctor Maybe Source # 
Instance details

Defined in Data.Comp.Param.Term

Methods

termM :: (forall a. Maybe (Trm f a)) -> Maybe (Term f) Source #

ParamFunctor (Either a) Source # 
Instance details

Defined in Data.Comp.Param.Term

Methods

termM :: (forall a0. Either a (Trm f a0)) -> Either a (Term f) Source #