| Portability | GADTs, Rank2Types | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | None | 
Control.Applicative.Trans.Free
Contents
Description
Applicative functor transformers for free
- newtype ApT f g a = ApT {}
- data ApF f g a where
- liftApT :: Applicative g => f a -> ApT f g a
- liftApO :: Functor g => g a -> 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
- runApF :: (Applicative h, Functor g) => (forall a. f a -> h a) -> (forall a. g (h a) -> h a) -> ApF f g b -> h b
- runApT_ :: (Functor g, Monoid m) => (forall a. f a -> m) -> (g m -> m) -> ApT f g b -> m
- hoistApT :: Functor g => (forall a. f a -> f' a) -> ApT f g b -> ApT f' g b
- hoistApF :: Functor g => (forall a. f a -> f' a) -> ApF f g b -> ApF f' g b
- transApT :: Functor g => (forall a. g a -> g' a) -> ApT f g b -> ApT f g' b
- transApF :: Functor g => (forall a. g a -> g' a) -> ApF f g b -> ApF f g' b
- type Ap f = ApT f Identity
- runAp :: Applicative g => (forall x. f x -> g x) -> Ap f a -> g a
- runAp_ :: Monoid m => (forall x. f x -> m) -> Ap f a -> m
- retractAp :: Applicative f => Ap f a -> f a
- type Alt f = ApT f []
- runAlt :: (Alternative g, Foldable t) => (forall x. f x -> g x) -> ApT f t a -> g a
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.
The free Applicative transformer for a Functor f over
 Applicative g.
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) | 
The free Applicative for a Functor f.
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.
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.
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
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 fg.
runAp t == retractApp . hoistApp t
retractAp :: Applicative f => Ap f a -> f aSource
Free Alternative
The free Alternative for a Functor f.