operational-alacarte-0.3.1: A version of Operational suitable for extensible EDSLs

Safe HaskellSafe
LanguageHaskell2010

Data.ALaCarte

Contents

Description

This module provides a generalized implementation of data types à la carte [1]. It supports (higher-order) functors with 0 or more functorial parameters and additional non-functorial parameters, all with a uniform interface.

\[1\] W. Swierstra. Data Types à la Carte. Journal of Functional Programming, 18(4):423-436, 2008, http://dx.doi.org/10.1017/S0956796808006758.

(This module is preferably used with the GHC extensions DataKinds and PolyKinds.)

Usage

Compared to traditional data types à la carte, an extra poly-kinded parameter has been added to :+: and to the parameters of :<:. Standard data types à la carte is obtained by setting this parameter to (). That gives us the following type for Inl:

Inl :: h1 () a -> (h1 :+: h2) () a

Here, h1 () and (h1 :+: h2) () are functors.

By setting the extra parameter to a functor f :: * -> *, we obtain this type:

Inl :: h1 f a -> (h1 :+: h2) f a

This makes h1 and (h1 :+: h2) higher-order functors.

Finally, by setting the parameter to a type-level pair of functors '(f,g) :: (* -> *, * -> *), we obtain this type:

Inl :: h1 '(f,g) a -> (h1 :+: h2) '(f,g) a

This makes h1 and (h1 :+: h2) higher-order bi-functors.

Alternatively, we can represent all three cases above using heterogeneous lists of functors constructed using '(,) and terminated by ():

Inl :: h1 ()           a -> (h1 :+: h2) ()           a  -- functor
Inl :: h1 '(f,())      a -> (h1 :+: h2) '(f,())      a  -- higher-order functor
Inl :: h1 '(f,'(g,())) a -> (h1 :+: h2) '(f,'(g,())) a  -- higher-order bi-functor

This view is taken by the classes HFunctor and HBifunctor. An HFunctor takes a parameter of kind (* -> *, k); i.e. it has at least one functorial parameter. A HBiFunctor takes a parameter of kind (* -> *, (* -> *, k)); i.e. it has at least two functorial parameters.

Aliases for parameter lists

To avoid ugly types such as '(f,'(g,())), this module exports the synonyms Param0, Param1, Param2, etc. for parameter lists up to size 4. These synonyms allow the module to be used without the DataKinds extension.

Extra type parameters

Recall that an HFunctor takes a parameter of kind (* -> *, k), and an HBifunctor takes a parameter of kind (* -> *, (* -> *, k)). Since k is polymorphic, it means that it is possible to add extra parameters in place of k.

For example, a user can define the following type representing addition in some language:

data Add fs a where
  Add :: (Num a, pred a) => f a -> f a -> Add (Param2 f pred) a

instance HFunctor Add where
  hfmap f (Add a b) = Add (f a) (f b)

Here, Add has a functorial parameter f, and an extra non-functorial parameter pred that provides a constraint for the type a.

An obvious alternative would have been to just make pred a separate parameter to Add:

data Add pred fs a where
  Add :: (Num a, pred a) => f a -> f a -> Add pred (Param1 f) a

instance HFunctor (Add pred) where
  hfmap f (Add a b) = Add (f a) (f b)

However, this has the disadvantage of being hard to use together with the :<: class. For example, we might want to define the following "smart constructor" for Add:

mkAdd :: (Num a, pred a, Add pred :<: h) => f a -> f a -> h (Param1 f) a
mkAdd a b = inj (Add a b)

Unfortunately, the above type is ambiguous, because pred is completely free. Assuming that h is a type of the form (... :+: Add Show :+: ...), we would like to infer (pred ~ Show), but this would require extra machinery, such as a type family that computes pred from h.

By putting pred in the parameter list, we avoid the above problem. We also get the advantage that the same pred parameter is distributed to all types in a sum constructed using :+:. This makes it easier to, for example, change the pred parameter uniformly throughout an expression.

Synopsis

Documentation

data (h1 :+: h2) fs a infixr 9 Source #

Coproducts

Constructors

Inl (h1 fs a) 
Inr (h2 fs a) 

Instances

(HBifunctor k k1 k2 h1, HBifunctor k k1 k2 h2) => HBifunctor k k1 k2 ((:+:) k (* -> *, (k1 -> *, k2)) h1 h2) Source # 

Methods

hbimap :: (Functor f, Functor g) => (forall b. f b -> g b) -> (forall b. i b -> j b) -> h ((* -> *, (k -> *, k)) f ((k -> *, k) i fs)) a -> h ((* -> *, (k -> *, k)) g ((k -> *, k) j fs)) a Source #

(HFunctor k k1 k2 h1, HFunctor k k1 k2 h2) => HFunctor k k1 k2 ((:+:) k (k1 -> *, k2) h1 h2) Source # 

Methods

hfmap :: (forall b. f b -> g b) -> h ((k -> *, k) f fs) a -> h ((k -> *, k) g fs) a Source #

(:<:) k k1 f h => (:<:) k k1 f ((:+:) k k1 g h) Source # 

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

(:<:) k k1 f ((:+:) k k1 f g) Source # 

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

(Reexpressible k k1 i1 instr env, Reexpressible k k1 i2 instr env) => Reexpressible k k1 ((:+:) * (* -> *, (k -> *, k1)) i1 i2) instr env Source # 

Methods

reexpressInstrEnv :: Monad m => (forall b. exp1 b -> ReaderT * env (ProgramT ((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) instr (((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) exp2 fs) m) (exp2 b)) -> env ((* -> *, ((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr)) (ReaderT * env (ProgramT ((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) instr (((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) exp2 fs) m)) (((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) exp1 fs)) a -> ReaderT * env (ProgramT ((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) instr (((* :+: (* -> *, (k -> *, k1))) i1 i2 -> *, instr) exp2 fs) m) a Source #

(InterpBi k k1 i1 m fs, InterpBi k k1 i2 m fs) => InterpBi k k1 ((:+:) k (k -> *, (k -> *, k1)) i1 i2) m fs Source # 

Methods

interpBi :: fs (((k :+: (k -> *, (k -> *, k1))) i1 i2 -> *, ((k :+: (k -> *, (k -> *, k1))) i1 i2 -> *, m)) m (((k :+: (k -> *, (k -> *, k1))) i1 i2 -> *, m) m fs)) a -> m a Source #

(Interp k k1 i1 m fs, Interp k k1 i2 m fs) => Interp k k1 ((:+:) k (k -> *, k1) i1 i2) m fs Source # 

Methods

interp :: fs (((k :+: (k -> *, k1)) i1 i2 -> *, m) m fs) a -> m a Source #

(Functor (h2 fs), Functor (h1 fs)) => Functor ((:+:) * k h1 h2 fs) Source # 

Methods

fmap :: (a -> b) -> (* :+: k) h1 h2 fs a -> (* :+: k) h1 h2 fs b #

(<$) :: a -> (* :+: k) h1 h2 fs b -> (* :+: k) h1 h2 fs a #

class sub :<: sup where Source #

A constraint f :<: g expresses that the signature f is subsumed by g, i.e. f can be used to construct elements in g.

Minimal complete definition

inj, prj

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

Instances

(:<:) k k1 f f Source # 

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

(:<:) k k1 f h => (:<:) k k1 f ((:+:) k k1 g h) Source # 

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

(:<:) k k1 f ((:+:) k k1 f g) Source # 

Methods

inj :: sub fs a -> sup fs a Source #

prj :: sup fs a -> Maybe (sub fs a) Source #

class HFunctor h where Source #

Higher-order functors

Minimal complete definition

hfmap

Methods

hfmap :: (forall b. f b -> g b) -> h '(f, fs) a -> h '(g, fs) a Source #

Higher-order fmap

Instances

(HFunctor k k1 k2 h1, HFunctor k k1 k2 h2) => HFunctor k k1 k2 ((:+:) k (k1 -> *, k2) h1 h2) Source # 

Methods

hfmap :: (forall b. f b -> g b) -> h ((k -> *, k) f fs) a -> h ((k -> *, k) g fs) a Source #

class HFunctor h => HBifunctor h where Source #

Higher-order bi-functors

Minimal complete definition

hbimap

Methods

hbimap :: (Functor f, Functor g) => (forall b. f b -> g b) -> (forall b. i b -> j b) -> h '(f, '(i, fs)) a -> h '(g, '(j, fs)) a Source #

Higher-order "bimap"

Instances

(HBifunctor k k1 k2 h1, HBifunctor k k1 k2 h2) => HBifunctor k k1 k2 ((:+:) k (* -> *, (k1 -> *, k2)) h1 h2) Source # 

Methods

hbimap :: (Functor f, Functor g) => (forall b. f b -> g b) -> (forall b. i b -> j b) -> h ((* -> *, (k -> *, k)) f ((k -> *, k) i fs)) a -> h ((* -> *, (k -> *, k)) g ((k -> *, k) j fs)) a Source #

Parameter lists

type Param0 = () Source #

Empty parameter list

type Param1 a = '(a, Param0) Source #

Singleton parameter list

type Param2 a b = '(a, Param1 b) Source #

Two-element parameter list

type Param3 a b c = '(a, Param2 b c) Source #

Three-element parameter list

type Param4 a b c d = '(a, Param3 b c d) Source #

Four-element parameter list