effet-0.3.0.1: 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.Embed

Contents

Description

The embed effect for integrating arbitrary monads into the effect system.

Synopsis

Tagged Embed Effect

class Monad m => Embed' tag n m | tag m -> n where Source #

An effect that integrates a monad n into the computation m.

Since: 0.3.0.0

Methods

embed' :: n a -> m a Source #

Monadic actions in n can be lifted into m via embed.

embed is like liftIO, but not limited to IO. In fact, liftIO can be realized using embed by specializing n to IO.

Since: 0.3.0.0

Instances
Embed' (tag :: k) Identity Identity Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: Identity a -> Identity a Source #

Embed' (tag :: k) [] [] Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: [a] -> [a] Source #

Embed' (tag :: k) Maybe Maybe Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: Maybe a -> Maybe a Source #

Embed' (tag :: k) IO IO Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: IO a -> IO a Source #

Monad n => Embed' (tag :: k) n (Finalization n) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> Finalization n a Source #

Handle (Embed' tag n) t m => Embed' (tag :: k) n (EachVia (Embed' tag n ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> EachVia (Embed' tag n ': effs) t m a Source #

Find (Embed' tag n) effs t m => Embed' (tag :: k) n (EachVia (other ': effs) t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> EachVia (other ': effs) t m a Source #

Lift (Embed' tag n) t m => Embed' (tag :: k) n (EachVia ([] :: [Effect]) t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> EachVia [] t m a Source #

Embed' tag t m => Embed' (tag :: k) n (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> Transformation n t m a Source #

Embed' new n m => Embed' (tag :: k2) n (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> Tagger tag new m a Source #

Untagged Embed Effect

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

type Embed n = Embed' G n Source #

embed :: Embed n m => n a -> m a Source #

Interpretations

Via Transformation

data Transformation n t m a Source #

The transformation interpreter of the embed effect. This type implements the Embed type class by transforming the integrated monad n into another integrated monad t via natural transformation.

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

Instances
Embed' tag t m => Embed' (tag :: k) n (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> Transformation n t m a Source #

MonadBase b m => MonadBase b (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftBase :: b α -> Transformation n t m α #

MonadBaseControl b m => MonadBaseControl b (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type StM (Transformation n t m) a :: Type #

Methods

liftBaseWith :: (RunInBase (Transformation n t m) b -> b a) -> Transformation n t m a #

restoreM :: StM (Transformation n t m) a -> Transformation n t m a #

MonadTrans (Transformation n t) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

lift :: Monad m => m a -> Transformation n t m a #

MonadTransControl (Transformation n t) Source # 
Instance details

Defined in Control.Effect.Embed

Associated Types

type StT (Transformation n t) a :: Type #

Methods

liftWith :: Monad m => (Run (Transformation n t) -> m a) -> Transformation n t m a #

restoreT :: Monad m => m (StT (Transformation n t) a) -> Transformation n t m a #

Monad m => Monad (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

(>>=) :: Transformation n t m a -> (a -> Transformation n t m b) -> Transformation n t m b #

(>>) :: Transformation n t m a -> Transformation n t m b -> Transformation n t m b #

return :: a -> Transformation n t m a #

fail :: String -> Transformation n t m a #

Functor m => Functor (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

fmap :: (a -> b) -> Transformation n t m a -> Transformation n t m b #

(<$) :: a -> Transformation n t m b -> Transformation n t m a #

Applicative m => Applicative (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

pure :: a -> Transformation n t m a #

(<*>) :: Transformation n t m (a -> b) -> Transformation n t m a -> Transformation n t m b #

liftA2 :: (a -> b -> c) -> Transformation n t m a -> Transformation n t m b -> Transformation n t m c #

(*>) :: Transformation n t m a -> Transformation n t m b -> Transformation n t m b #

(<*) :: Transformation n t m a -> Transformation n t m b -> Transformation n t m a #

MonadIO m => MonadIO (Transformation n t m) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

liftIO :: IO a -> Transformation n t m a #

type StT (Transformation n t) a Source # 
Instance details

Defined in Control.Effect.Embed

type StT (Transformation n t) a
type StM (Transformation n t m) a Source # 
Instance details

Defined in Control.Effect.Embed

type StM (Transformation n t m) a

runEmbed' Source #

Arguments

:: (forall b. n b -> t b)

The natural transformation from monad n to monad t.

-> (Embed' tag n `Via` Transformation n t) m a

The program whose embed effect should be handled.

-> m a

The program with its embed effect handled.

Runs the embed effect by transforming the integrated monad n into another integrated monad t.

Since: 0.3.0.0

runEmbed :: (forall b. n b -> t b) -> (Embed n `Via` Transformation n t) m a -> m a Source #

The untagged version of runEmbed'.

Via Finalization

data Finalization m a Source #

The finalization interpreter of the embed effect. This type implements the Embed type class by declaring the integrated monad the final monad m (also called the "base monad").

Chances are very high that you only need this interpreter if you have a custom final monad because the Embed' effect is already implemented for final monads like IO, Maybe, [] and Identity.

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

Since: 0.3.0.0

Instances
Monad n => Embed' (tag :: k) n (Finalization n) Source # 
Instance details

Defined in Control.Effect.Embed

Methods

embed' :: n a -> Finalization n a Source #

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

Defined in Control.Effect.Embed

Methods

liftBase :: b α -> Finalization m α #

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

Defined in Control.Effect.Embed

Associated Types

type StM (Finalization m) a :: Type #

Methods

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

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

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

Defined in Control.Effect.Embed

Methods

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

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

Defined in Control.Effect.Embed

Associated Types

type StT Finalization a :: Type #

Methods

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

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

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

Defined in Control.Effect.Embed

Methods

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

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

return :: a -> Finalization m a #

fail :: String -> Finalization m a #

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

Defined in Control.Effect.Embed

Methods

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

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

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

Defined in Control.Effect.Embed

Methods

pure :: a -> Finalization m a #

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

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

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

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

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

Defined in Control.Effect.Embed

Methods

liftIO :: IO a -> Finalization m a #

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

Defined in Control.Effect.Embed

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

Defined in Control.Effect.Embed

type StM (Finalization m) a = StM m a

runFinal' Source #

Arguments

:: (Embed' tag m `Via` Finalization) m a

The program whose embed effect should be handled.

-> m a

The program with its embed effect handled.

Runs the embed effect by declaring the integrated monad the final monad.

Since: 0.3.0.0

runFinal :: (Embed m `Via` Finalization) m a -> m a Source #

The untagged version of runFinal'.

Since: 0.3.0.0

Tagging and Untagging

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

    tagEmbed' @"newTag" program
    retagEmbed' @"oldTag" @"newTag" program
    untagEmbed' @"erasedTag" program

tagEmbed' :: forall new n m a. Via (Embed' G n) (Tagger G new) m a -> m a Source #

retagEmbed' :: forall tag new n m a. Via (Embed' tag n) (Tagger tag new) m a -> m a Source #

untagEmbed' :: forall tag n m a. Via (Embed' tag n) (Tagger tag G) m a -> m a Source #