| Copyright | (C) 2008-2016 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | non-portable (rank-2 polymorphism) | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Control.Monad.Codensity
Contents
Description
Synopsis
- newtype Codensity (m :: k -> TYPE rep) a = Codensity {- runCodensity :: forall b. (a -> m b) -> m b
 
- lowerCodensity :: Applicative f => Codensity f a -> f a
- codensityToAdjunction :: Adjunction f g => Codensity g a -> g (f a)
- adjunctionToCodensity :: Adjunction f g => g (f a) -> Codensity g a
- codensityToRan :: Codensity g a -> Ran g g a
- ranToCodensity :: Ran g g a -> Codensity g a
- codensityToComposedRep :: Representable u => Codensity u a -> u (Rep u, a)
- composedRepToCodensity :: Representable u => u (Rep u, a) -> Codensity u a
- wrapCodensity :: (forall a. m a -> m a) -> Codensity m ()
- improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f a
- reset :: Monad m => Codensity m a -> Codensity m a
- shift :: Applicative m => (forall b. (a -> m b) -> Codensity m b) -> Codensity m a
Documentation
newtype Codensity (m :: k -> TYPE rep) a Source #
Codensity fFunctor f along itself (Ran f f).
This can often be more "efficient" to construct than f itself using
 repeated applications of (>>=).
See "Asymptotic Improvement of Computations over Free Monads" by Janis Voigtländer for more information about this type.
https://www.janis-voigtlaender.eu/papers/AsymptoticImprovementOfComputationsOverFreeMonads.pdf
Constructors
| Codensity | |
| Fields 
 | |
Instances
| (m ~~ m', Functor f, MonadFree f m') => MonadFree f (Codensity m) Source # | |
| Defined in Control.Monad.Codensity | |
| (m ~~ m', MonadReader r m') => MonadReader r (Codensity m) Source # | |
| (m ~~ m', MonadReader r m') => MonadState r (Codensity m) Source # | |
| MonadTrans (Codensity :: (Type -> Type) -> Type -> Type) Source # | |
| Defined in Control.Monad.Codensity | |
| (f ~~ f', MonadFail f') => MonadFail (Codensity f) Source # | |
| Defined in Control.Monad.Codensity | |
| (m ~~ m', MonadIO m') => MonadIO (Codensity m) Source # | |
| Defined in Control.Monad.Codensity | |
| (v ~~ v', Alternative v') => Alternative (Codensity v) Source # | |
| Applicative (Codensity f) Source # | |
| Defined in Control.Monad.Codensity | |
| Functor (Codensity k) Source # | |
| Monad (Codensity f) Source # | |
| (v ~~ v', Alternative v') => MonadPlus (Codensity v) Source # | |
| (v ~~ v', Alt v') => Alt (Codensity v) Source # | |
| Apply (Codensity f) Source # | |
| (v ~~ v', Plus v') => Plus (Codensity v) Source # | |
| Defined in Control.Monad.Codensity | |
lowerCodensity :: Applicative f => Codensity f a -> f a Source #
This serves as the *left*-inverse (retraction) of lift.
lowerCodensity.lift≡id
In general this is not a full 2-sided inverse, merely a retraction, as
 Codensity mm.
e.g. Codensity ((->) s)) a ~ forall r. (a -> s -> r) -> s -> rMonadState s(->) s
 is limited to MonadReader s
codensityToAdjunction :: Adjunction f g => Codensity g a -> g (f a) Source #
The Codensity monad of a right adjoint is isomorphic to the
 monad obtained from the Adjunction.
codensityToAdjunction.adjunctionToCodensity≡idadjunctionToCodensity.codensityToAdjunction≡id
adjunctionToCodensity :: Adjunction f g => g (f a) -> Codensity g a Source #
codensityToRan :: Codensity g a -> Ran g g a Source #
The Codensity Monad of a Functor g is the right Kan extension (Ran)
 of g along itself.
codensityToRan.ranToCodensity≡idranToCodensity.codensityToRan≡id
ranToCodensity :: Ran g g a -> Codensity g a Source #
codensityToComposedRep :: Representable u => Codensity u a -> u (Rep u, a) Source #
The Codensity monad of a representable Functor is isomorphic to the
 monad obtained from the Adjunction for which that Functor is the right
 adjoint.
codensityToComposedRep.composedRepToCodensity≡idcomposedRepToCodensity.codensityToComposedRep≡id
codensityToComposedRep =ranToComposedRep.codensityToRan
composedRepToCodensity :: Representable u => u (Rep u, a) -> Codensity u a Source #
wrapCodensity :: (forall a. m a -> m a) -> Codensity m () Source #
Wrap the remainder of the Codensity action using the given
 function.
This function can be used to register cleanup actions that will be executed at the end. Example:
wrapCodensity (`finally` putStrLn "Done.")
improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f a Source #
Right associate all binds in a computation that generates a free monad
This can improve the asymptotic efficiency of the result, while preserving semantics.
See "Asymptotic Improvement of Computations over Free Monads" by Janis Voightländer for more information about this combinator.