-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Fast monads and monad transformers
--
-- Fast implementations of monads and monad transformers using right Kan
-- extensions
@package monad-ran
@version 0.1.0
-- | A fast right Kan extension based Monad Transformer that can be
-- used to generate an efficient CPS representation from any combination
-- of monads from the Monad Transformer Library.
--
-- To use, just wrap the type of your monad in Ran: i.e. Ran
-- (StateT MyState ReaderT MyEnv IO) Bool and use liftRan ::
-- RanFunctor m => m a -> Ran m a and and lowerRan ::
-- RanFunctor m => Ran m a -> m a to extract your original
-- monad.
--
-- This is really just a fancy way of saying that m a is isomorphic to
-- forall o. (a -> f o) -> g o for some definition of f and g that
-- is chosen by m. In practice f and g are built up out of newtypes.
--
-- Ran m a is often more efficient than the straightforward monad m
-- because CPS transforming can yield additional optimization
-- opportunities. There are a few caveats to be aware of however. If you
-- inspect the result multiple times then 'Ran m a' may have to recompute
-- its result for each usage. To prevent this, either, use 'Ran m a'
-- once, as in most straight-line monadic code, or explicitly call
-- lowerRan on it and perform your repeated tests against the
-- unlifted monad.
--
-- Since Ran m is a data type that depends on type families, Ran cannot
-- be made an instance of MonadTrans, use liftRanT or
-- inRan in place of lift as needed.
module Control.Monad.Ran
-- | A right Kan extension transformer for a monad
data Ran m a
Ran :: (forall b. (a -> G m b) -> H m b) -> Ran m a
getRan :: Ran m a -> forall b. (a -> G m b) -> H m b
class (Applicative (Ran f), Applicative f, RanFunctor f) => RanApplicative f
class (Monad (Ran f), Monad f, RanFunctor f) => RanMonad f
class RanFunctor f where { type family G f :: * -> *; type family H f :: * -> *; }
liftRan :: (RanFunctor f) => f a -> Ran f a
lowerRan :: (RanFunctor f) => Ran f a -> f a
class RanTrans t
liftRanT :: (RanTrans t, RanFunctor m, RanFunctor (t m)) => Ran m a -> Ran (t m) a
outRan :: (RanTrans t, RanFunctor m, RanFunctor (t m)) => Ran (t m) a -> t (Ran m) a
inRan :: (RanTrans t, RanFunctor m, RanFunctor (t m)) => t (Ran m) a -> Ran (t m) a
returnRanCodensity :: (RanFunctor m, (G m) ~ (H m)) => a -> Ran m a
bindRanCodensity :: (RanFunctor m, (G m) ~ (H m)) => Ran m a -> (a -> Ran m b) -> Ran m b
apRanCodensity :: (RanFunctor m, (G m) ~ (H m)) => Ran m (a -> b) -> Ran m a -> Ran m b
ranCodensity :: Ran (Codensity f) a -> Codensity f a
codensityRan :: Codensity f a -> Ran (Codensity f) a
liftRanCodensity :: (RanFunctor m, (G m) ~ (H m), Monad (G m)) => G m a -> Ran m a
lowerRanCodensity :: (RanFunctor m, (G m) ~ (H m), Monad (G m)) => Ran m a -> G m a
liftRanWorld :: ((G m) ~ (World w), (H m) ~ (World w)) => (State# w -> (# State# w, a #)) -> Ran m a
lowerRanWorld :: ((G m) ~ (World w), (H m) ~ (World w)) => Ran m a -> State# w -> (# State# w, a #)
-- | The Covariant Yoneda lemma applied to a functor. Note that f
-- need not be a Hask Functor!
data Yoneda f a
Yoneda :: (forall b. (a -> b) -> f b) -> Yoneda f a
getYoneda :: Yoneda f a -> forall b. (a -> b) -> f b
lowerYoneda :: Yoneda f a -> f a
-- | The Codensity monad of a functor/monad generated by a functor
data Codensity f a
Codensity :: (forall b. (a -> f b) -> f b) -> Codensity f a
getCodensity :: Codensity f a -> forall b. (a -> f b) -> f b
lowerCodensity :: (Monad m) => Codensity m a -> m a
lowerCodensityApp :: (Applicative f) => Codensity f a -> f a
instance [incoherent] MonadCont (Ran (ContT r m))
instance [incoherent] Monad (Ran (ContT r m))
instance [incoherent] RanFunctor (ContT r m)
instance [incoherent] MonadCont (Ran (Cont r))
instance [incoherent] Monad (Ran (Cont r))
instance [incoherent] Applicative (Ran (Cont r))
instance [incoherent] RanFunctor (Cont r)
instance [incoherent] (MonadFix m) => MonadFix (Yoneda m)
instance [incoherent] (MonadError e f) => MonadError e (Yoneda f)
instance [incoherent] (MonadRWS r w s f) => MonadRWS r w s (Yoneda f)
instance [incoherent] (MonadIO f) => MonadIO (Yoneda f)
instance [incoherent] (MonadState s f) => MonadState s (Yoneda f)
instance [incoherent] (MonadWriter w f) => MonadWriter w (Yoneda f)
instance [incoherent] (MonadReader r f) => MonadReader r (Yoneda f)
instance [incoherent] MonadTrans Yoneda
instance [incoherent] (MonadPlus f) => MonadPlus (Yoneda f)
instance [incoherent] (Monad f) => Monad (Yoneda f)
instance [incoherent] (Alternative f) => Alternative (Yoneda f)
instance [incoherent] (Applicative f) => Applicative (Yoneda f)
instance [incoherent] Functor (Yoneda f)
instance [incoherent] (MonadError e m) => MonadError e (Ran (Codensity m))
instance [incoherent] (MonadFix m) => MonadFix (Ran (Codensity m))
instance [incoherent] (MonadRWS r w s m) => MonadRWS r w s (Ran (Codensity m))
instance [incoherent] (MonadReader r m) => MonadReader r (Ran (Codensity m))
instance [incoherent] (MonadWriter w m) => MonadWriter w (Ran (Codensity m))
instance [incoherent] (MonadState s m) => MonadState s (Ran (Codensity m))
instance [incoherent] (MonadIO f) => MonadIO (Ran (Codensity f))
instance [incoherent] (MonadPlus f) => MonadPlus (Ran (Codensity f))
instance [incoherent] (Alternative (Codensity f)) => Alternative (Ran (Codensity f))
instance [incoherent] Monad (Ran (Codensity f))
instance [incoherent] Applicative (Ran (Codensity f))
instance [incoherent] RanFunctor (Codensity f)
instance [incoherent] MonadTrans Codensity
instance [incoherent] (MonadError e m) => MonadError e (Codensity m)
instance [incoherent] (MonadFix f) => MonadFix (Codensity f)
instance [incoherent] (MonadRWS r w s m) => MonadRWS r w s (Codensity m)
instance [incoherent] (MonadState s m) => MonadState s (Codensity m)
instance [incoherent] (MonadWriter w m) => MonadWriter w (Codensity m)
instance [incoherent] (MonadReader r m) => MonadReader r (Codensity m)
instance [incoherent] (MonadPlus m) => MonadPlus (Codensity m)
instance [incoherent] (MonadIO m) => MonadIO (Codensity m)
instance [incoherent] Monad (Codensity f)
instance [incoherent] Applicative (Codensity f)
instance [incoherent] Functor (Codensity k)
instance [incoherent] (RanMonad m, Monoid w, MonadFix (Ran m)) => MonadFix (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w, MonadPlus (Ran m)) => MonadPlus (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w, MonadIO (Ran m)) => MonadIO (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadReader r (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadWriter w (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadState s (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => Monad (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m), Monoid w) => Alternative (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => Applicative (Ran (RWST r w s m))
instance [incoherent] (Monoid w) => RanTrans (RWST r w s)
instance [incoherent] (Monoid w, RanFunctor m) => RanFunctor (RWST r w s m)
instance [incoherent] (RanMonad m, Monoid w, MonadFix (Ran m)) => MonadFix (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w, MonadPlus (Ran m)) => MonadPlus (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w, MonadIO (Ran m)) => MonadIO (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadReader r (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadWriter w (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => MonadState s (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => Monad (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m), Monoid w) => Alternative (Ran (RWST r w s m))
instance [incoherent] (RanMonad m, Monoid w) => Applicative (Ran (RWST r w s m))
instance [incoherent] (Monoid w) => RanTrans (RWST r w s)
instance [incoherent] (Monoid w, RanFunctor m) => RanFunctor (RWST r w s m)
instance [incoherent] (RanMonad m, MonadFix (Ran m)) => MonadFix (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => MonadPlus (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadIO (Ran m)) => MonadIO (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadReader e (Ran m)) => MonadReader e (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadWriter w (Ran m)) => MonadWriter w (Ran (StateT s m))
instance [incoherent] (RanMonad m) => MonadState s (Ran (StateT s m))
instance [incoherent] (RanMonad m) => Monad (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => Alternative (Ran (StateT s m))
instance [incoherent] (RanMonad m) => Applicative (Ran (StateT e m))
instance [incoherent] RanTrans (StateT s)
instance [incoherent] (RanFunctor m) => RanFunctor (StateT s m)
instance [incoherent] (RanMonad m, MonadFix (Ran m)) => MonadFix (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => MonadPlus (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadIO (Ran m)) => MonadIO (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadReader e (Ran m)) => MonadReader e (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadWriter w (Ran m)) => MonadWriter w (Ran (StateT s m))
instance [incoherent] (RanMonad m) => MonadState s (Ran (StateT s m))
instance [incoherent] (RanMonad m) => Monad (Ran (StateT s m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => Alternative (Ran (StateT s m))
instance [incoherent] (RanMonad m) => Applicative (Ran (StateT e m))
instance [incoherent] RanTrans (StateT s)
instance [incoherent] (RanFunctor m) => RanFunctor (StateT s m)
instance [incoherent] (Monoid w, RanMonad m, MonadFix (Ran m)) => MonadFix (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadPlus (Ran m)) => MonadPlus (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadIO (Ran m)) => MonadIO (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadReader e (Ran m)) => MonadReader e (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => MonadWriter w (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadState s (Ran m)) => MonadState s (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => Monad (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadPlus (Ran m)) => Alternative (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => Applicative (Ran (WriterT w m))
instance [incoherent] (Monoid w) => RanTrans (WriterT w)
instance [incoherent] (Monoid w, RanFunctor m) => RanFunctor (WriterT w m)
instance [incoherent] (Monoid w, RanMonad m, MonadFix (Ran m)) => MonadFix (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadPlus (Ran m)) => MonadPlus (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadIO (Ran m)) => MonadIO (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadReader e (Ran m)) => MonadReader e (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => MonadWriter w (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadState s (Ran m)) => MonadState s (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => Monad (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m, MonadPlus (Ran m)) => Alternative (Ran (WriterT w m))
instance [incoherent] (Monoid w, RanMonad m) => Applicative (Ran (WriterT w m))
instance [incoherent] (Monoid w) => RanTrans (WriterT w)
instance [incoherent] (Monoid w, RanFunctor m) => RanFunctor (WriterT w m)
instance [incoherent] (RanFunctor m, Read (Ran m (Either a b))) => Read (Ran (ErrorT a m) b)
instance [incoherent] (RanFunctor m, Show (Ran m (Either a b))) => Show (Ran (ErrorT a m) b)
instance [incoherent] (RanFunctor m, Ord (Ran m (Either a b))) => Ord (Ran (ErrorT a m) b)
instance [incoherent] (RanFunctor m, Eq (Ran m (Either a b))) => Eq (Ran (ErrorT a m) b)
instance [incoherent] (RanMonad m, Error e, MonadFix (Ran m)) => MonadFix (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadIO (Ran m)) => MonadIO (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadRWS r w s (Ran m)) => MonadRWS r w s (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadWriter w (Ran m)) => MonadWriter w (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadReader r (Ran m)) => MonadReader r (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadState s (Ran m)) => MonadState s (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e) => Monad (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e, MonadPlus (Ran m)) => Alternative (Ran (ErrorT e m))
instance [incoherent] (RanMonad m, Error e) => Applicative (Ran (ErrorT e m))
instance [incoherent] RanTrans (ErrorT e)
instance [incoherent] (RanFunctor m, Error e) => RanFunctor (ErrorT e m)
instance [incoherent] (RanMonad m, MonadFix (Ran m)) => MonadFix (Ran (ReaderT e m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => MonadPlus (Ran (ReaderT e m))
instance [incoherent] (RanMonad m, MonadIO (Ran m)) => MonadIO (Ran (ReaderT e m))
instance [incoherent] (RanMonad m, MonadWriter w (Ran m)) => MonadWriter w (Ran (ReaderT e m))
instance [incoherent] (RanMonad m) => MonadReader r (Ran (ReaderT r m))
instance [incoherent] (RanMonad m, MonadState s (Ran m)) => MonadState s (Ran (ReaderT e m))
instance [incoherent] (RanMonad m) => Monad (Ran (ReaderT e m))
instance [incoherent] (RanMonad m, MonadPlus (Ran m)) => Alternative (Ran (ReaderT e m))
instance [incoherent] (RanMonad m) => Applicative (Ran (ReaderT e m))
instance [incoherent] RanTrans (ReaderT e)
instance [incoherent] (RanFunctor m) => RanFunctor (ReaderT e m)
instance [incoherent] (Monoid m) => Monoid (Ran (Reader e) m)
instance [incoherent] MonadReader e (Ran (Reader e))
instance [incoherent] Monad (Ran (Reader e))
instance [incoherent] Applicative (Ran (Reader e))
instance [incoherent] RanFunctor (Reader e)
instance [incoherent] (Monoid m) => Monoid (Ran ((->) e) m)
instance [incoherent] MonadReader e (Ran ((->) e))
instance [incoherent] Monad (Ran ((->) e))
instance [incoherent] Applicative (Ran ((->) e))
instance [incoherent] RanFunctor ((->) e)
instance [incoherent] (Read a, Read b) => Read (Ran (Either a) b)
instance [incoherent] (Show a, Show b) => Show (Ran (Either a) b)
instance [incoherent] (Ord a, Ord b) => Ord (Ran (Either a) b)
instance [incoherent] (Eq a, Eq b) => Eq (Ran (Either a) b)
instance [incoherent] (Error e) => MonadFix (Ran (Either e))
instance [incoherent] (Error e) => MonadPlus (Ran (Either e))
instance [incoherent] (Error e) => MonadError e (Ran (Either e))
instance [incoherent] (Error e) => Monad (Ran (Either e))
instance [incoherent] RanFunctor (Either e)
instance [incoherent] (Read a) => Read (Ran Maybe a)
instance [incoherent] (Show a) => Show (Ran Maybe a)
instance [incoherent] (Ord a) => Ord (Ran Maybe a)
instance [incoherent] (Eq a) => Eq (Ran Maybe a)
instance [incoherent] MonadFix (Ran Maybe)
instance [incoherent] (Monoid a) => Monoid (Ran Maybe a)
instance [incoherent] MonadPlus (Ran Maybe)
instance [incoherent] Applicative (Ran Maybe)
instance [incoherent] Monad (Ran Maybe)
instance [incoherent] RanFunctor Maybe
instance [incoherent] (MonadFix m) => MonadFix (Ran (Yoneda m))
instance [incoherent] (MonadError e f) => MonadError e (Ran (Yoneda f))
instance [incoherent] (MonadRWS r w s f) => MonadRWS r w s (Ran (Yoneda f))
instance [incoherent] (MonadIO f) => MonadIO (Ran (Yoneda f))
instance [incoherent] (MonadState s f) => MonadState s (Ran (Yoneda f))
instance [incoherent] (MonadWriter w f) => MonadWriter w (Ran (Yoneda f))
instance [incoherent] (MonadReader r f) => MonadReader r (Ran (Yoneda f))
instance [incoherent] (MonadPlus f) => MonadPlus (Ran (Yoneda f))
instance [incoherent] (Monad f) => Monad (Ran (Yoneda f))
instance [incoherent] (Alternative f) => Alternative (Ran (Yoneda f))
instance [incoherent] (Applicative f) => Applicative (Ran (Yoneda f))
instance [incoherent] RanFunctor (Yoneda f)
instance [incoherent] Monad (Ran STM)
instance [incoherent] Applicative (Ran STM)
instance [incoherent] RanFunctor STM
instance [incoherent] MonadFix (Ran (ST s))
instance [incoherent] Monad (Ran (ST s))
instance [incoherent] Applicative (Ran (ST s))
instance [incoherent] RanFunctor (ST s)
instance [incoherent] MonadFix (Ran IO)
instance [incoherent] MonadError IOError (Ran IO)
instance [incoherent] MonadPlus (Ran IO)
instance [incoherent] MonadIO (Ran IO)
instance [incoherent] Monad (Ran IO)
instance [incoherent] Applicative (Ran IO)
instance [incoherent] RanFunctor IO
instance [incoherent] (Monoid w) => MonadWriter w (Ran (Writer w))
instance [incoherent] (Monoid w) => Monad (Ran (Writer w))
instance [incoherent] (Monoid w) => Applicative (Ran (Writer w))
instance [incoherent] (Monoid w) => RanFunctor (Writer w)
instance [incoherent] MonadState s (Ran (State s))
instance [incoherent] Monad (Ran (State s))
instance [incoherent] Applicative (Ran (State s))
instance [incoherent] RanFunctor (State s)
instance [incoherent] (Read a) => Read (Ran Identity a)
instance [incoherent] (Show a) => Show (Ran Identity a)
instance [incoherent] (Ord a) => Ord (Ran Identity a)
instance [incoherent] (Eq a) => Eq (Ran Identity a)
instance [incoherent] Monad (Ran Identity)
instance [incoherent] Applicative (Ran Identity)
instance [incoherent] RanFunctor Identity
instance [incoherent] (Applicative (Ran f), Applicative f, RanFunctor f) => RanApplicative f
instance [incoherent] (Monad (Ran f), Monad f, RanFunctor f) => RanMonad f
instance [incoherent] (RanFunctor f) => Functor (Ran f)