shade-0.1.1.1: A control structure used to combine heterogenous types with delayed effects.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Shade

Description

A control structure used to combine heterogenous types with delayed effects.

Synopsis

Documentation

class MonadShade m where Source #

Minimal complete definition

shade, transfer

Methods

shade :: c a -> (a -> b) -> m c b Source #

Insert a contextual value and its projection into a shade.

transfer :: MonadShade m => (forall a. c0 a -> c1 a) -> m c0 t -> m c1 t Source #

Changed the context of a hidden value. The first argument must be universally quantified since no assumptions may be made as to what value is stored inside the shade.

Instances

MonadShade ShadeT Source # 

Methods

shade :: c a -> (a -> b) -> ShadeT c b Source #

transfer :: MonadShade ShadeT => (forall a. c0 a -> c1 a) -> ShadeT c0 t -> ShadeT c1 t Source #

data ShadeT m b Source #

A shade consists of a hidden value and an image of that value. The hidden values are stored in a context and cannot be accessed directly.

Instances

MonadTrans ShadeT Source # 

Methods

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

MonadShade ShadeT Source # 

Methods

shade :: c a -> (a -> b) -> ShadeT c b Source #

transfer :: MonadShade ShadeT => (forall a. c0 a -> c1 a) -> ShadeT c0 t -> ShadeT c1 t Source #

MonadError e m => MonadError e (ShadeT m) Source # 

Methods

throwError :: e -> ShadeT m a #

catchError :: ShadeT m a -> (e -> ShadeT m a) -> ShadeT m a #

MonadReader s m => MonadReader s (ShadeT m) Source # 

Methods

ask :: ShadeT m s #

local :: (s -> s) -> ShadeT m a -> ShadeT m a #

reader :: (s -> a) -> ShadeT m a #

MonadState s m => MonadState s (ShadeT m) Source # 

Methods

get :: ShadeT m s #

put :: s -> ShadeT m () #

state :: (s -> (a, s)) -> ShadeT m a #

MonadWriter s m => MonadWriter s (ShadeT m) Source # 

Methods

writer :: (a, s) -> ShadeT m a #

tell :: s -> ShadeT m () #

listen :: ShadeT m a -> ShadeT m (a, s) #

pass :: ShadeT m (a, s -> s) -> ShadeT m a #

Monad m => Monad (ShadeT m) Source #

m >>= f applies f to the projected value inside the original context of m. The result is the a shade which becomes the source object in the result. This resut is nested twice inside the same context, and these are joined together.

Methods

(>>=) :: ShadeT m a -> (a -> ShadeT m b) -> ShadeT m b #

(>>) :: ShadeT m a -> ShadeT m b -> ShadeT m b #

return :: a -> ShadeT m a #

fail :: String -> ShadeT m a #

Functor (ShadeT m) Source #

fmap applies a function to the result of the projected value inside the values original context.

Methods

fmap :: (a -> b) -> ShadeT m a -> ShadeT m b #

(<$) :: a -> ShadeT m b -> ShadeT m a #

Applicative m => Applicative (ShadeT m) Source #

pure is the identity projection of the original value stored in a pure context.

a <*> b combines the contexts of the hidden values and applies the shadow of b value onto the shadow of a.

Methods

pure :: a -> ShadeT m a #

(<*>) :: ShadeT m (a -> b) -> ShadeT m a -> ShadeT m b #

(*>) :: ShadeT m a -> ShadeT m b -> ShadeT m b #

(<*) :: ShadeT m a -> ShadeT m b -> ShadeT m a #

Monad m => MonadZip (ShadeT m) Source # 

Methods

mzip :: ShadeT m a -> ShadeT m b -> ShadeT m (a, b) #

mzipWith :: (a -> b -> c) -> ShadeT m a -> ShadeT m b -> ShadeT m c #

munzip :: ShadeT m (a, b) -> (ShadeT m a, ShadeT m b) #

MonadIO m => MonadIO (ShadeT m) Source # 

Methods

liftIO :: IO a -> ShadeT m a #

Alternative m => Alternative (ShadeT m) Source # 

Methods

empty :: ShadeT m a #

(<|>) :: ShadeT m a -> ShadeT m a -> ShadeT m a #

some :: ShadeT m a -> ShadeT m [a] #

many :: ShadeT m a -> ShadeT m [a] #

(Applicative m, Monoid b) => Monoid (ShadeT m b) Source #

mempty is simply the shadow and source of the neutral element of the stored value.

mappend combines the contexts of two shadows and mappends their stored values.

Methods

mempty :: ShadeT m b #

mappend :: ShadeT m b -> ShadeT m b -> ShadeT m b #

mconcat :: [ShadeT m b] -> ShadeT m b #

shade :: MonadShade m => c a -> (a -> b) -> m c b Source #

Insert a contextual value and its projection into a shade.

hide :: MonadShade m => c a -> m c a Source #

Hide a boxed value inside a shade with the identity as projection.

shadow :: Functor m => ShadeT m b -> m b Source #

The projection of the hidden value (the "shadow").

transfer :: (MonadShade m, MonadShade m) => (forall a. c0 a -> c1 a) -> m c0 t -> m c1 t Source #

Changed the context of a hidden value. The first argument must be universally quantified since no assumptions may be made as to what value is stored inside the shade.