free-5.0.2: Monads for free

Copyright(C) 2012-2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityGADTs, Rank2Types
Safe HaskellSafe
LanguageHaskell2010

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

Instances

Functor g => Functor (ApT f g) Source # 

Methods

fmap :: (a -> b) -> ApT f g a -> ApT f g b #

(<$) :: a -> ApT f g b -> ApT f g a #

Applicative g => Applicative (ApT f g) Source # 

Methods

pure :: a -> ApT f g a #

(<*>) :: ApT f g (a -> b) -> ApT f g a -> ApT f g b #

liftA2 :: (a -> b -> c) -> ApT f g a -> ApT f g b -> ApT f g c #

(*>) :: ApT f g a -> ApT f g b -> ApT f g b #

(<*) :: ApT f g a -> ApT f g b -> ApT f g a #

Alternative g => Alternative (ApT f g) Source # 

Methods

empty :: ApT f g a #

(<|>) :: ApT f g a -> ApT f g a -> ApT f g a #

some :: ApT f g a -> ApT f g [a] #

many :: ApT f g a -> ApT f g [a] #

Applicative g => Apply (ApT f g) Source # 

Methods

(<.>) :: ApT f g (a -> b) -> ApT f g a -> ApT f g b #

(.>) :: ApT f g a -> ApT f g b -> ApT f g b #

(<.) :: ApT f g a -> ApT f g b -> ApT f g a #

liftF2 :: (a -> b -> c) -> ApT f g a -> ApT f g b -> ApT f g c #

data ApF f g a where Source #

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) Source # 

Methods

fmap :: (a -> b) -> ApF f g a -> ApF f g b #

(<$) :: a -> ApF f g b -> ApF f g a #

Applicative g => Applicative (ApF f g) Source # 

Methods

pure :: a -> ApF f g a #

(<*>) :: ApF f g (a -> b) -> ApF f g a -> ApF f g b #

liftA2 :: (a -> b -> c) -> ApF f g a -> ApF f g b -> ApF f g c #

(*>) :: ApF f g a -> ApF f g b -> ApF f g b #

(<*) :: ApF f g a -> ApF f g b -> ApF f g a #

Applicative g => Apply (ApF f g) Source # 

Methods

(<.>) :: ApF f g (a -> b) -> ApF f g a -> ApF f g b #

(.>) :: ApF f g a -> ApF f g b -> ApF f g b #

(<.) :: ApF f g a -> ApF f g b -> ApF f g a #

liftF2 :: (a -> b -> c) -> ApF f g a -> ApF f g b -> ApF f g c #

liftApT :: Applicative g => f a -> ApT f g a Source #

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

liftApO :: Functor g => g a -> ApT f g a Source #

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 b Source #

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 b Source #

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 -> m Source #

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 b Source #

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 b Source #

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' b Source #

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' b Source #

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

joinApT :: Monad m => ApT f m a -> m (Ap f a) Source #

Pull out and join m layers of ApT f m a.

Free Applicative

type Ap f = ApT f Identity Source #

The free Applicative for a Functor f.

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

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 -> m Source #

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 a Source #

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 a Source #

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