polysemy-1.0.0.0: Higher-order, low-boilerplate, zero-cost free monads.

Safe HaskellNone
LanguageHaskell2010

Polysemy.Internal.Tactics

Synopsis

Documentation

data Tactics f n r m a where Source #

Constructors

GetInitialState :: Tactics f n r m (f ()) 
HoistInterpretation :: (a -> n b) -> Tactics f n r m (f a -> Sem r (f b)) 
GetInspector :: Tactics f n r m (Inspector f) 

getInitialStateT :: forall f m r e. Sem (WithTactics e f m r) (f ()) Source #

Get the stateful environment of the world at the moment the effect e is to be run. Prefer pureT, runT or bindT instead of using this function directly.

getInspectorT :: forall e f m r. Sem (WithTactics e f m r) (Inspector f) Source #

Get a natural transformation capable of potentially inspecting values inside of f. Binding the result of getInspectorT produces a function that can sometimes peek inside values returned by bindT.

This is often useful for running callback functions that are not managed by polysemy code.

Example

We can use the result of getInspectT to "undo" pureT (or any of the other Tactical functions):

ins <- getInspectorT
fa <- pureT "hello"
fb <- pureT True
let a = inspect ins fa   -- Just "hello"
    b = inspect ins fb   -- Just True

We

newtype Inspector f Source #

A container for inspect. See the documentation for getInspectorT.

Constructors

Inspector 

Fields

runT Source #

Arguments

:: m a

The monadic action to lift. This is usually a parameter in your effect.

-> Sem (WithTactics e f m r) (Sem (e ': r) (f a)) 

Run a monadic action in a Tactical environment. The stateful environment used will be the same one that the effect is initally run in. Use bindT if you'd prefer to explicitly manage your stateful environment.

bindT Source #

Arguments

:: (a -> m b)

The monadic continuation to lift. This is usually a parameter in your effect.

Continuations lifted via bindT will run in the same environment which produced the a.

-> Sem (WithTactics e f m r) (f a -> Sem (e ': r) (f b)) 

Lift a kleisli action into the stateful environment. You can use bindT to get an effect parameter of the form a -> m b into something that can be used after calling runT on an effect parameter m a.

pureT :: a -> Tactical e m r a Source #

Lift a value into Tactical.

liftT :: forall m f r e a. Functor f => Sem r a -> Sem (WithTactics e f m r) (f a) Source #

Internal function to create first-order interpreter combinators out of higher-order ones.

runTactics :: Functor f => f () -> (forall x. f (m x) -> Sem r2 (f x)) -> (forall x. f x -> Maybe x) -> Sem (Tactics f m r2 ': r) a -> Sem r a Source #

Run the Tactics effect.

type Tactical e m r x = forall f. Functor f => Sem (WithTactics e f m r) (f x) Source #

Tactical is an environment in which you're capable of explicitly threading higher-order effect states. This is provided by the (internal) effect Tactics, which is capable of rewriting monadic actions so they run in the correct stateful environment.

Inside a Tactical, you're capable of running pureT, runT and bindT which are the main tools for rewriting monadic stateful environments.

For example, consider trying to write an interpreter for Resource, whose effect is defined as:

data Resource m a where
  Bracket :: m a -> (a -> m ()) -> (a -> m b) -> Resource m b

Here we have an m a which clearly needs to be run first, and then subsequently call the a -> m () and a -> m b arguments. In a Tactical environment, we can write the threading code thusly:

Bracket alloc dealloc use -> do
  alloc'   <- runT  alloc
  dealloc' <- bindT dealloc
  use'     <- bindT use

where

alloc'   ::         Sem (Resource ': r) (f a1)
dealloc' :: f a1 -> Sem (Resource ': r) (f ())
use'     :: f a1 -> Sem (Resource ': r) (f x)

The f type here is existential and corresponds to "whatever state the other effects want to keep track of." f is always a Functor.

alloc', dealloc' and use' are now in a form that can be easily consumed by your interpreter. At this point, simply bind them in the desired order and continue on your merry way.

We can see from the types of dealloc' and use' that since they both consume a f a1, they must run in the same stateful environment. This means, for illustration, any puts run inside the use block will not be visible inside of the dealloc block.

Power users may explicitly use getInitialStateT and bindT to construct whatever data flow they'd like; although this is usually unnecessary.

type WithTactics e f m r = Tactics f m (e ': r) ': r Source #