kan-extensions-5.2.1: Kan extensions, Kan lifts, the Yoneda lemma, and (co)density (co)monads

Copyright(C) 2008-2016 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilitynon-portable (rank-2 polymorphism)
Safe HaskellTrustworthy
LanguageHaskell2010

Control.Monad.Codensity

Description

 
Synopsis

Documentation

newtype Codensity (m :: k -> TYPE rep) a Source #

Codensity f is the Monad generated by taking the right Kan extension of any Functor 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 # 
Instance details

Defined in Control.Monad.Codensity

Methods

ask :: Codensity m r #

local :: (r -> r) -> Codensity m a -> Codensity m a #

reader :: (r -> a) -> Codensity m a #

MonadReader r m => MonadState r (Codensity m) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

get :: Codensity m r #

put :: r -> Codensity m () #

state :: (r -> (a, r)) -> Codensity m a #

(Functor f, MonadFree f m) => MonadFree f (Codensity m) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

wrap :: f (Codensity m a) -> Codensity m a #

MonadTrans (Codensity :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

lift :: Monad m => m a -> Codensity m a #

Monad (Codensity f) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

(>>=) :: Codensity f a -> (a -> Codensity f b) -> Codensity f b #

(>>) :: Codensity f a -> Codensity f b -> Codensity f b #

return :: a -> Codensity f a #

fail :: String -> Codensity f a #

Functor (Codensity k) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

fmap :: (a -> b) -> Codensity k a -> Codensity k b #

(<$) :: a -> Codensity k b -> Codensity k a #

MonadFail f => MonadFail (Codensity f) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

fail :: String -> Codensity f a #

Applicative (Codensity f) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

pure :: a -> Codensity f a #

(<*>) :: Codensity f (a -> b) -> Codensity f a -> Codensity f b #

liftA2 :: (a -> b -> c) -> Codensity f a -> Codensity f b -> Codensity f c #

(*>) :: Codensity f a -> Codensity f b -> Codensity f b #

(<*) :: Codensity f a -> Codensity f b -> Codensity f a #

MonadIO m => MonadIO (Codensity m) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

liftIO :: IO a -> Codensity m a #

Alternative v => Alternative (Codensity v) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

empty :: Codensity v a #

(<|>) :: Codensity v a -> Codensity v a -> Codensity v a #

some :: Codensity v a -> Codensity v [a] #

many :: Codensity v a -> Codensity v [a] #

Alternative v => MonadPlus (Codensity v) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

mzero :: Codensity v a #

mplus :: Codensity v a -> Codensity v a -> Codensity v a #

Plus v => Plus (Codensity v) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

zero :: Codensity v a #

Alt v => Alt (Codensity v) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

(<!>) :: Codensity v a -> Codensity v a -> Codensity v a #

some :: Applicative (Codensity v) => Codensity v a -> Codensity v [a] #

many :: Applicative (Codensity v) => Codensity v a -> Codensity v [a] #

Apply (Codensity f) Source # 
Instance details

Defined in Control.Monad.Codensity

Methods

(<.>) :: Codensity f (a -> b) -> Codensity f a -> Codensity f b #

(.>) :: Codensity f a -> Codensity f b -> Codensity f b #

(<.) :: Codensity f a -> Codensity f b -> Codensity f a #

liftF2 :: (a -> b -> c) -> Codensity f a -> Codensity f b -> Codensity f c #

lowerCodensity :: Applicative f => Codensity f a -> f a Source #

This serves as the *left*-inverse (retraction) of lift.

lowerCodensity . liftid

In general this is not a full 2-sided inverse, merely a retraction, as Codensity m is often considerably "larger" than m.

e.g. Codensity ((->) s)) a ~ forall r. (a -> s -> r) -> s -> r could support a full complement of MonadState s actions, while (->) s is limited to MonadReader s actions.

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 . adjunctionToCodensityid
adjunctionToCodensity . codensityToAdjunctionid

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 . ranToCodensityid
ranToCodensity . codensityToRanid

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 . composedRepToCodensityid
composedRepToCodensity . codensityToComposedRepid
codensityToComposedRep = ranToComposedRep . codensityToRan

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.

http://www.iai.uni-bonn.de/~jv/mpc08.pdf