simple-effects-0.13.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Newtype

Description

Sometimes it's useful to give a new name to an already existing effect. This module provides the tools to make that easy to do.

Synopsis

Documentation

effectAsNewtype :: forall newtyped original m a. (MonadEffect newtyped m, Coercible (newtyped m) (original m)) => RuntimeImplemented original m a -> m a Source #

If we have a computation using some effect original, we can convert it into a computation that uses the effect newtyped instead. Provided, of course, that newtyped is really a newtype over the original effect.

f :: MonadEffect (State Int) m => m ()
f = getState >>= i -> setState (i + 1)

newtype MyState m = MyState (State Int m)

-- inferred: g :: MonadEffect MyState m => m ()
g = effectAsNewtype @MyState @(State Int) f

newtype EffTag (tag :: k) e (m :: * -> *) Source #

A useful newtype for any effect. Just provide a unique tag, like a type level string.

Constructors

EffTag (e m) 
Instances
Effect e => Effect (EffTag tag e) Source # 
Instance details

Defined in Control.Effects.Newtype

Associated Types

type CanLift (EffTag tag e) t :: Constraint Source #

type ExtraConstraint (EffTag tag e) m :: Constraint Source #

Methods

liftThrough :: (CanLift (EffTag tag e) t, Monad m, Monad (t m)) => EffTag tag e m -> EffTag tag e (t m) Source #

mergeContext :: Monad m => m (EffTag tag e m) -> EffTag tag e m Source #

(e ~ e', Effect e, Monad m, CanLift e (RuntimeImplemented (EffTag tag e))) => MonadEffect (EffTag tag e) (RuntimeImplemented (EffTag tag e') m) Source # 
Instance details

Defined in Control.Effects.Newtype

Methods

effect :: EffTag tag e (RuntimeImplemented (EffTag tag e') m) Source #

type CanLift (EffTag tag e) t Source # 
Instance details

Defined in Control.Effects.Newtype

type CanLift (EffTag tag e) t = CanLift e t
type ExtraConstraint (EffTag tag e) m Source # 
Instance details

Defined in Control.Effects.Newtype

type ExtraConstraint (EffTag tag e) m = ()

tagEffect :: forall tag original m a. MonadEffect (EffTag tag original) m => RuntimeImplemented original m a -> m a Source #

Rename an effect without explicitly declaring a new newtype. Just provide a tag. This is useful if you have two functions using the same effect that you want to combine but you don't want their effects to interact. For example, maybe they both work with Int states but you don't want them to modify each other's number.

implementTagged :: forall tag original m a. original m -> RuntimeImplemented (EffTag tag original) m a -> m a Source #

Once you tag your effect, it's slightly inconvenient that you have to wrap your implementation when you want to handle it. This function doees the wrapping for you.

f :: MonadEffect (State Int) m => m ()
f = getState >>= \s -> setState (s * 2)

g :: MonadEffect (State Int) m => m ()
g = getState >>= \s -> setState (s * 3)

combine :: Monad m => m Int
combine =
    implementStateViaStateT 5 $ implementTagged @"s2" (StateMethods getState setState)
    $ implementStateViaStateT 0 $ implementTagged @"s1" (StateMethods getState setState)
    $ do
    r1 <- tagEffect @"s1" @(State Int) (f >> getState)
    r2 <- tagEffect @"s2" @(State Int) (g >> getState)
    return (r1 + r2) -- results in 15