effet-0.1.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.RWS

Description

The effect that combines the reader, writer and state effect, similar to the MonadRWS type class from the mtl library.

Lazy and strict interpretations of the effect are available here: Control.Effect.RWS.Lazy and Control.Effect.RWS.Strict.

Synopsis

Tagged RWS Effect

class Monad m => RWS' tag r w s m | tag m -> r w s where Source #

An effect that adds the following features to a given computation:

  • (R) an immutable environment (the "reader" part)
  • (W) a write-only, accumulated output (the "writer" part)
  • (S) a mutable state (the "state" part)

Methods

ask' :: m r Source #

Gets the environment.

local' Source #

Arguments

:: (r -> r)

The function to modify the environment.

-> m a

The sub-computation to run in the modified environment.

-> m a

The result of the sub-computation.

Executes a sub-computation in a modified environment.

tell' :: w -> m () Source #

Produces the output w. In other words, w is appended to the accumulated output.

listen' :: m a -> m (w, a) Source #

Executes a sub-computation and appends w to the accumulated output.

censor' Source #

Arguments

:: (w -> w)

The function which is applied to the output.

-> m a

The sub-computation which produces the modified output.

-> m a

The result of the sub-computation.

Executes a sub-computation and applies the function to its output.

get' :: m s Source #

Gets the current state.

put' :: s -> m () Source #

Replaces the state with a new value.

Instances

Instances details
(Reader' tag r m, Writer' tag w m, State' tag s m) => RWS' (tag :: k) r w s (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: Separation m r Source #

local' :: (r -> r) -> Separation m a -> Separation m a Source #

tell' :: w -> Separation m () Source #

listen' :: Separation m a -> Separation m (w, a) Source #

censor' :: (w -> w) -> Separation m a -> Separation m a Source #

get' :: Separation m s Source #

put' :: s -> Separation m () Source #

Control (RWS' tag r w s) t m => RWS' (tag :: k) r w s (Via eff t m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: Via eff t m r Source #

local' :: (r -> r) -> Via eff t m a -> Via eff t m a Source #

tell' :: w -> Via eff t m () Source #

listen' :: Via eff t m a -> Via eff t m (w, a) Source #

censor' :: (w -> w) -> Via eff t m a -> Via eff t m a Source #

get' :: Via eff t m s Source #

put' :: s -> Via eff t m () Source #

Handle (RWS' tag r w s) t m => RWS' (tag :: k) r w s (Via (RWS' tag r w s) t m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: Via (RWS' tag r w s) t m r Source #

local' :: (r -> r) -> Via (RWS' tag r w s) t m a -> Via (RWS' tag r w s) t m a Source #

tell' :: w -> Via (RWS' tag r w s) t m () Source #

listen' :: Via (RWS' tag r w s) t m a -> Via (RWS' tag r w s) t m (w, a) Source #

censor' :: (w -> w) -> Via (RWS' tag r w s) t m a -> Via (RWS' tag r w s) t m a Source #

get' :: Via (RWS' tag r w s) t m s Source #

put' :: s -> Via (RWS' tag r w s) t m () Source #

(Monad m, Monoid w) => RWS' (tag :: k) r w s (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: RWST r w s m r Source #

local' :: (r -> r) -> RWST r w s m a -> RWST r w s m a Source #

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

get' :: RWST r w s m s Source #

put' :: s -> RWST r w s m () Source #

(Monad m, Monoid w) => RWS' (tag :: k) r w s (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: RWST r w s m r Source #

local' :: (r -> r) -> RWST r w s m a -> RWST r w s m a Source #

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

get' :: RWST r w s m s Source #

put' :: s -> RWST r w s m () Source #

(Monad m, Monoid w) => RWS' (tag :: k) r w s (RWST r w s m) Source # 
Instance details

Defined in Control.Effect.RWS.Strict

Methods

ask' :: RWST r w s m r Source #

local' :: (r -> r) -> RWST r w s m a -> RWST r w s m a Source #

tell' :: w -> RWST r w s m () Source #

listen' :: RWST r w s m a -> RWST r w s m (w, a) Source #

censor' :: (w -> w) -> RWST r w s m a -> RWST r w s m a Source #

get' :: RWST r w s m s Source #

put' :: s -> RWST r w s m () Source #

RWS' new r w s m => RWS' (tag :: k2) r w s (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: Tagger tag new m r Source #

local' :: (r -> r) -> Tagger tag new m a -> Tagger tag new m a Source #

tell' :: w -> Tagger tag new m () Source #

listen' :: Tagger tag new m a -> Tagger tag new m (w, a) Source #

censor' :: (w -> w) -> Tagger tag new m a -> Tagger tag new m a Source #

get' :: Tagger tag new m s Source #

put' :: s -> Tagger tag new m () Source #

Untagged RWS Effect

If you don't require disambiguation of multiple RWS effects (i.e., you only have one RWS effect in your monadic context), it is recommended to always use the untagged RWS effect.

type RWS r w s = RWS' G r w s Source #

ask :: RWS r w s m => m r Source #

local :: RWS r w s m => (r -> r) -> m a -> m a Source #

tell :: RWS r w s m => w -> m () Source #

listen :: RWS r w s m => m a -> m (w, a) Source #

censor :: RWS r w s m => (w -> w) -> m a -> m a Source #

get :: RWS r w s m => m s Source #

put :: RWS r w s m => s -> m () Source #

Convenience Functions

Reader Convenience

If you don't require disambiguation of multiple RWS effects (i.e., you only have one RWS effect in your monadic context), it is recommended to always use the untagged functions.

asks' Source #

Arguments

:: forall tag r w s m a. RWS' tag r w s m 
=> (r -> a)

The projection function to apply to the environment.

-> m a

The result of the projection.

Gets a specific component of the environment, using the provided projection function.

asks :: RWS r w s m => (r -> a) -> m a Source #

The untagged version of asks'.

Writer Convenience

If you don't require disambiguation of multiple RWS effects (i.e., you only have one RWS effect in your monadic context), it is recommended to always use the untagged functions.

listens' Source #

Arguments

:: forall tag r w s b m a. RWS' tag r w s m 
=> (w -> b)

The function which is applied to the output.

-> m a

The sub-computation which produces the modified output.

-> m (b, a)

The result of the sub-computation, including the modified output.

Executes a sub-computation and applies the function to its output, thus adding an additional value to the result of the sub-computation.

listens :: RWS r w s m => (w -> b) -> m a -> m (b, a) Source #

The untagged version of listens'.

State Convenience

If you don't require disambiguation of multiple RWS effects (i.e., you only have one RWS effect in your monadic context), it is recommended to always use the untagged functions.

gets' :: forall tag r w s m a. RWS' tag r w s m => (s -> a) -> m a Source #

Gets a specific component of the state, using the provided projection function.

gets :: RWS r w s m => (s -> a) -> m a Source #

The untagged version of gets'.

modify' :: forall tag r w s m. RWS' tag r w s m => (s -> s) -> m () Source #

Modifies the state, using the provided function.

modify :: RWS r w s m => (s -> s) -> m () Source #

The untagged version of modify'.

modifyStrict' :: forall tag r w s m. RWS' tag r w s m => (s -> s) -> m () Source #

Modifies the state, using the provided function. The computation is strict in the new state.

modifyStrict :: RWS r w s m => (s -> s) -> m () Source #

The untagged version of modifyStrict'.

Interpretations

newtype Separation m a Source #

The separation interpreter of the RWS effect. This type implements the RWS' type class by splitting the effect into separate Reader', Writer' and State' effects which can then be interpreted individually.

When interpreting the effect, you usually don't interact with this type directly, but instead use one of its corresponding interpretation functions.

Constructors

Separation 

Fields

Instances

Instances details
(Reader' tag r m, Writer' tag w m, State' tag s m) => RWS' (tag :: k) r w s (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

ask' :: Separation m r Source #

local' :: (r -> r) -> Separation m a -> Separation m a Source #

tell' :: w -> Separation m () Source #

listen' :: Separation m a -> Separation m (w, a) Source #

censor' :: (w -> w) -> Separation m a -> Separation m a Source #

get' :: Separation m s Source #

put' :: s -> Separation m () Source #

MonadBase b m => MonadBase b (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

liftBase :: b α -> Separation m α #

MonadBaseControl b m => MonadBaseControl b (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Associated Types

type StM (Separation m) a #

Methods

liftBaseWith :: (RunInBase (Separation m) b -> b a) -> Separation m a #

restoreM :: StM (Separation m) a -> Separation m a #

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

Defined in Control.Effect.RWS

Methods

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

MonadTransControl (Separation :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Effect.RWS

Associated Types

type StT Separation a #

Methods

liftWith :: Monad m => (Run Separation -> m a) -> Separation m a #

restoreT :: Monad m => m (StT Separation a) -> Separation m a #

Monad m => Monad (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

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

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

return :: a -> Separation m a #

Functor m => Functor (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

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

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

Applicative m => Applicative (Separation m) Source # 
Instance details

Defined in Control.Effect.RWS

Methods

pure :: a -> Separation m a #

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

liftA2 :: (a -> b -> c) -> Separation m a -> Separation m b -> Separation m c #

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

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

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

Defined in Control.Effect.RWS

Methods

liftIO :: IO a -> Separation m a #

type StT (Separation :: (Type -> Type) -> Type -> Type) a Source # 
Instance details

Defined in Control.Effect.RWS

type StT (Separation :: (Type -> Type) -> Type -> Type) a = StT (Default :: (Type -> Type) -> Type -> Type) a
type StM (Separation m) a Source # 
Instance details

Defined in Control.Effect.RWS

type StM (Separation m) a = StM m a

runSeparatedRWS' Source #

Arguments

:: (RWS' tag r w s `Via` Separation) m a

The program whose RWS effect should be handled.

-> m a

The program with its RWS effect handled.

Runs the RWS effect via separation.

runSeparatedRWS :: (RWS r w s `Via` Separation) m a -> m a Source #

The untagged version of runSeparatedRWS'.

Tagging and Untagging

Conversion functions between the tagged and untagged RWS effect, usually used in combination with type applications, like:

    tagRWS' @"newTag" program
    retagRWS' @"oldTag" @"newTag" program
    untagRWS' @"erasedTag" program

tagRWS' :: forall new r w s m a. Via (RWS' G r w s) (Tagger G new) m a -> m a Source #

retagRWS' :: forall tag new r w s m a. Via (RWS' tag r w s) (Tagger tag new) m a -> m a Source #

untagRWS' :: forall tag r w s m a. Via (RWS' tag r w s) (Tagger tag G) m a -> m a Source #