constrained-normal-1.0.2: Normalised Deep Embeddings for Constrained Type-Class Instances

Portabilityghc
Stabilityalpha
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Safe HaskellNone

Control.Monad.ConstrainedNormal

Contents

Description

This module provides constrained normalised type classes. The ideas behind this module are documented in the following paper:

The Constrained-Monad Problem. Neil Sculthorpe and Jan Bracker and George Giorgidze and Andy Gill. International Conference on Functional Programming, pages 287-298. ACM, 2013. http://dx.doi.org/10.1145/2500365.2500602

Synopsis

Constrained Normalised Functors

data NF whereSource

Constructors

FMap :: c x => (x -> a) -> t x -> NF c t a 

Instances

Functor (NF c t) 

liftNF :: c a => t a -> NF c t aSource

lowerNF :: (forall x. c x => (x -> a) -> t x -> t a) -> NF c t a -> t aSource

foldNF :: (forall x. c x => (x -> a) -> t x -> r) -> NF c t a -> rSource

Constrained Normalised Pointed Functors

class Functor f => PointedFunctor f whereSource

Methods

point :: a -> f aSource

Instances

data NPF whereSource

Constructors

Point :: a -> NPF c t a 
Functor :: NF c t a -> NPF c t a 

Instances

Functor (NPF c t) 
PointedFunctor (NPF c t) 

liftNPF :: c a => t a -> NPF c t aSource

lowerNPF :: (a -> t a) -> (forall x. c x => (x -> a) -> t x -> t a) -> NPF c t a -> t aSource

foldNPF :: (a -> r) -> (forall x. c x => (x -> a) -> t x -> r) -> NPF c t a -> rSource

Constrained Normalised Applicative Functors

data NAF whereSource

Constructors

Pure :: a -> NAF c t a 
Ap :: c x => NAF c t (x -> a) -> t x -> NAF c t a 

Instances

liftNAF :: c a => t a -> NAF c t aSource

lowerNAF :: (forall x. x -> t x) -> (forall y z. c y => t (y -> z) -> t y -> t z) -> NAF c t a -> t aSource

foldNAF :: forall a c r t. (forall x. x -> r x) -> (forall y z. c y => r (y -> z) -> t y -> r z) -> NAF c t a -> r aSource

Constrained Normalised Monads

data NM whereSource

Constructors

Return :: a -> NM c t a 
Bind :: c x => t x -> (x -> NM c t a) -> NM c t a 

Instances

Monad (NM c t) 
Functor (NM c t) 
Applicative (NM c t) 
PointedFunctor (NM c t) 

liftNM :: c a => t a -> NM c t aSource

lowerNM :: forall a c t. (a -> t a) -> (forall x. c x => t x -> (x -> t a) -> t a) -> NM c t a -> t aSource

foldNM :: forall a c r t. (a -> r) -> (forall x. c x => t x -> (x -> r) -> r) -> NM c t a -> rSource

Constrained Normalised MonadPlus

data NMP c t a Source

Constructors

MZero 
MPlus (NMP' c t a) (NMP c t a) 

Instances

Monad (NMP c t) 
Functor (NMP c t) 
MonadPlus (NMP c t) 
Applicative (NMP c t) 
Alternative (NMP c t) 
PointedFunctor (NMP c t) 

data NMP' whereSource

Constructors

MPReturn :: a -> NMP' c t a 
MPBind :: c x => t x -> (x -> NMP c t a) -> NMP' c t a 

liftNMP :: c a => t a -> NMP c t aSource

lowerNMP :: forall a c t. t a -> (t a -> t a -> t a) -> (a -> t a) -> (forall x. c x => t x -> (x -> t a) -> t a) -> NMP c t a -> t aSource

foldNMP :: forall a c r t. r -> (r -> r -> r) -> (a -> r) -> (forall x. c x => t x -> (x -> r) -> r) -> NMP c t a -> rSource

Utilities

class Unconstrained a Source

An empty type class. This can be used when a parameter of kind * -> Constraint is needed, but no constraints need to be imposed.

Instances