| 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 | Haskell98 | 
Control.Monad.Codensity
Description
- newtype Codensity m 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
- improve :: Functor f => (forall m. MonadFree f m => m a) -> Free f a
Documentation
newtype Codensity m 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
| MonadReader r m => MonadReader r (Codensity * m) Source # | |
| MonadReader r m => MonadState r (Codensity * m) Source # | |
| (Functor f, MonadFree f m) => MonadFree f (Codensity * m) Source # | |
| MonadTrans (Codensity *) Source # | |
| Monad (Codensity k f) Source # | |
| Functor (Codensity k1 k2) Source # | |
| MonadFail f => MonadFail (Codensity * f) Source # | |
| Applicative (Codensity k f) Source # | |
| MonadIO m => MonadIO (Codensity * m) Source # | |
| Alternative v => Alternative (Codensity * v) Source # | |
| Alternative v => MonadPlus (Codensity * v) Source # | |
| Plus v => Plus (Codensity * v) Source # | |
| Alt v => Alt (Codensity * v) Source # | |
| Apply (Codensity k f) Source # | |
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 #
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.