comonad-5.0.5: Comonads

Copyright(C) 2008-2013 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Control.Comonad.Trans.Env

Contents

Description

The environment comonad holds a value along with some retrievable context.

This module specifies the environment comonad transformer (aka coreader), which is left adjoint to the reader comonad.

The following sets up an experiment that retains its initial value in the background:

>>> let initial = env 0 0

Extract simply retrieves the value:

>>> extract initial
0

Play around with the value, in our case producing a negative value:

>>> let experiment = fmap (+ 10) initial
>>> extract experiment
10

Oh noes, something went wrong, 10 isn't very negative! Better restore the initial value using the default:

>>> let initialRestored = experiment =>> ask
>>> extract initialRestored
0
Synopsis

The strict environment comonad

type Env e = EnvT e Identity Source #

env :: e -> a -> Env e a Source #

Create an Env using an environment and a value

runEnv :: Env e a -> (e, a) Source #

The strict environment comonad transformer

data EnvT e w a Source #

Constructors

EnvT e (w a) 
Instances
ComonadTraced m w => ComonadTraced m (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Traced.Class

Methods

trace :: m -> EnvT e w a -> a Source #

ComonadStore s w => ComonadStore s (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Store.Class

Methods

pos :: EnvT e w a -> s Source #

peek :: s -> EnvT e w a -> a Source #

peeks :: (s -> s) -> EnvT e w a -> a Source #

seek :: s -> EnvT e w a -> EnvT e w a Source #

seeks :: (s -> s) -> EnvT e w a -> EnvT e w a Source #

experiment :: Functor f => (s -> f s) -> EnvT e w a -> f a Source #

Comonad w => ComonadEnv e (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Env.Class

Methods

ask :: EnvT e w a -> e Source #

ComonadHoist (EnvT e) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

cohoist :: (Comonad w, Comonad v) => (forall x. w x -> v x) -> EnvT e w a -> EnvT e v a Source #

ComonadTrans (EnvT e) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

lower :: Comonad w => EnvT e w a -> w a Source #

Functor w => Functor (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

fmap :: (a -> b) -> EnvT e w a -> EnvT e w b #

(<$) :: a -> EnvT e w b -> EnvT e w a #

(Monoid e, Applicative m) => Applicative (EnvT e m) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

pure :: a -> EnvT e m a #

(<*>) :: EnvT e m (a -> b) -> EnvT e m a -> EnvT e m b #

liftA2 :: (a -> b -> c) -> EnvT e m a -> EnvT e m b -> EnvT e m c #

(*>) :: EnvT e m a -> EnvT e m b -> EnvT e m b #

(<*) :: EnvT e m a -> EnvT e m b -> EnvT e m a #

Foldable w => Foldable (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

fold :: Monoid m => EnvT e w m -> m #

foldMap :: Monoid m => (a -> m) -> EnvT e w a -> m #

foldr :: (a -> b -> b) -> b -> EnvT e w a -> b #

foldr' :: (a -> b -> b) -> b -> EnvT e w a -> b #

foldl :: (b -> a -> b) -> b -> EnvT e w a -> b #

foldl' :: (b -> a -> b) -> b -> EnvT e w a -> b #

foldr1 :: (a -> a -> a) -> EnvT e w a -> a #

foldl1 :: (a -> a -> a) -> EnvT e w a -> a #

toList :: EnvT e w a -> [a] #

null :: EnvT e w a -> Bool #

length :: EnvT e w a -> Int #

elem :: Eq a => a -> EnvT e w a -> Bool #

maximum :: Ord a => EnvT e w a -> a #

minimum :: Ord a => EnvT e w a -> a #

sum :: Num a => EnvT e w a -> a #

product :: Num a => EnvT e w a -> a #

Traversable w => Traversable (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

traverse :: Applicative f => (a -> f b) -> EnvT e w a -> f (EnvT e w b) #

sequenceA :: Applicative f => EnvT e w (f a) -> f (EnvT e w a) #

mapM :: Monad m => (a -> m b) -> EnvT e w a -> m (EnvT e w b) #

sequence :: Monad m => EnvT e w (m a) -> m (EnvT e w a) #

(Semigroup e, ComonadApply w) => ComonadApply (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

(<@>) :: EnvT e w (a -> b) -> EnvT e w a -> EnvT e w b Source #

(@>) :: EnvT e w a -> EnvT e w b -> EnvT e w b Source #

(<@) :: EnvT e w a -> EnvT e w b -> EnvT e w a Source #

Comonad w => Comonad (EnvT e w) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

extract :: EnvT e w a -> a Source #

duplicate :: EnvT e w a -> EnvT e w (EnvT e w a) Source #

extend :: (EnvT e w a -> b) -> EnvT e w a -> EnvT e w b Source #

(Data e, Typeable w, Data (w a), Data a) => Data (EnvT e w a) Source # 
Instance details

Defined in Control.Comonad.Trans.Env

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EnvT e w a -> c (EnvT e w a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EnvT e w a) #

toConstr :: EnvT e w a -> Constr #

dataTypeOf :: EnvT e w a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EnvT e w a)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (EnvT e w a)) #

gmapT :: (forall b. Data b => b -> b) -> EnvT e w a -> EnvT e w a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EnvT e w a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EnvT e w a -> r #

gmapQ :: (forall d. Data d => d -> u) -> EnvT e w a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EnvT e w a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EnvT e w a -> m (EnvT e w a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EnvT e w a -> m (EnvT e w a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EnvT e w a -> m (EnvT e w a) #

runEnvT :: EnvT e w a -> (e, w a) Source #

lowerEnvT :: EnvT e w a -> w a Source #

Gets rid of the environment. This differs from extract in that it will not continue extracting the value from the contained comonad.

Combinators

ask :: EnvT e w a -> e Source #

Retrieves the environment.

asks :: (e -> f) -> EnvT e w a -> f Source #

Like ask, but modifies the resulting value with a function.

asks = f . ask

local :: (e -> e') -> EnvT e w a -> EnvT e' w a Source #

Modifies the environment using the specified function.