free-4.8.0.1: Monads for free

PortabilityGADTs, Rank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellNone

Control.Applicative.Trans.Free

Contents

Description

Applicative functor transformers for free

Synopsis

Documentation

Compared to the free monad transformers, they are less expressive. However, they are also more flexible to inspect and interpret, as the number of ways in which the values can be nested is more limited.

See Free Applicative Functors, by Paolo Capriotti and Ambrus Kaposi, for some applications.

newtype ApT f g a Source

The free Applicative transformer for a Functor f over Applicative g.

Constructors

ApT 

Fields

getApT :: g (ApF f g a)
 

Instances

Functor g => Functor (ApT f g) 
(Typeable1 f, Typeable1 g) => Typeable1 (ApT f g) 
Applicative g => Applicative (ApT f g) 
Alternative g => Alternative (ApT f g) 
Applicative g => Apply (ApT f g) 

data ApF f g a whereSource

The free Applicative for a Functor f.

Constructors

Pure :: a -> ApF f g a 
Ap :: f a -> ApT f g (a -> b) -> ApF f g b 

Instances

Functor g => Functor (ApF f g) 
(Typeable1 f, Typeable1 g) => Typeable1 (ApF f g) 
Applicative g => Applicative (ApF f g) 
Applicative g => Apply (ApF f g) 

liftApT :: Applicative g => f a -> ApT f g aSource

A version of lift that can be used with no constraint for f.

liftApO :: Functor g => g a -> ApT f g aSource

Lift an action of the "outer" Functor g a to ApT f g a.

runApT :: (Applicative h, Functor g) => (forall a. f a -> h a) -> (forall a. g (h a) -> h a) -> ApT f g b -> h bSource

Given natural transformations f ~> h and g . h ~> h this gives a natural transformation ApT f g ~> h.

runApF :: (Applicative h, Functor g) => (forall a. f a -> h a) -> (forall a. g (h a) -> h a) -> ApF f g b -> h bSource

Given natural transformations f ~> h and g . h ~> h this gives a natural transformation ApF f g ~> h.

runApT_ :: (Functor g, Monoid m) => (forall a. f a -> m) -> (g m -> m) -> ApT f g b -> mSource

Perform a monoidal analysis over ApT f g b value.

Examples:

 height :: (Functor g, Foldable g) => ApT f g a -> Int
 height = getSum . runApT_ (_ -> Sum 1) maximum
 size :: (Functor g, Foldable g) => ApT f g a -> Int
 size = getSum . runApT_ (_ -> Sum 1) fold

hoistApT :: Functor g => (forall a. f a -> f' a) -> ApT f g b -> ApT f' g bSource

Given a natural transformation from f to f' this gives a monoidal natural transformation from ApT f g to ApT f' g.

hoistApF :: Functor g => (forall a. f a -> f' a) -> ApF f g b -> ApF f' g bSource

Given a natural transformation from f to f' this gives a monoidal natural transformation from ApF f g to ApF f' g.

transApT :: Functor g => (forall a. g a -> g' a) -> ApT f g b -> ApT f g' bSource

Given a natural transformation from g to g' this gives a monoidal natural transformation from ApT f g to ApT f g'.

transApF :: Functor g => (forall a. g a -> g' a) -> ApF f g b -> ApF f g' bSource

Given a natural transformation from g to g' this gives a monoidal natural transformation from ApF f g to ApF f g'.

Free Applicative

type Ap f = ApT f IdentitySource

The free Applicative for a Functor f.

runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g aSource

Given a natural transformation from f to g, this gives a canonical monoidal natural transformation from Ap f to g.

runAp t == retractApp . hoistApp t

runAp_ :: Monoid m => (forall x. f x -> m) -> Ap f a -> mSource

Perform a monoidal analysis over free applicative value.

Example:

 count :: Ap f a -> Int
 count = getSum . runAp_ (\_ -> Sum 1)

retractAp :: Applicative f => Ap f a -> f aSource

Interprets the free applicative functor over f using the semantics for pure and <*> given by the Applicative instance for f.

retractApp == runAp id

Free Alternative

type Alt f = ApT f []Source

The free Alternative for a Functor f.

runAlt :: (Alternative g, Foldable t) => (forall x. f x -> g x) -> ApT f t a -> g aSource

Given a natural transformation from f to g, this gives a canonical monoidal natural transformation from Alt f to g.