extensible-effects-5.0.0.0: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010

Control.Eff.Fresh

Description

Create unique Enumerable values.

Synopsis

Documentation

data Fresh v where Source #

Create unique Enumerable values.

Constructors

Fresh :: Fresh Int 
Instances
Handle Fresh r a (Int -> k) Source #

Given a continuation and requests, respond to them

Instance details

Defined in Control.Eff.Fresh

Methods

handle :: (Eff r a -> Int -> k) -> Arrs r v a -> Fresh v -> Int -> k Source #

handle_relay :: (r ~ (Fresh ': r'), Relay (Int -> k) r') => (a -> Int -> k) -> (Eff r a -> Int -> k) -> Eff r a -> Int -> k Source #

respond_relay :: (a -> Int -> k) -> (Eff r a -> Int -> k) -> Eff r a -> Int -> k Source #

(MonadBase m m, LiftedBase m r) => MonadBaseControl m (Eff (Fresh ': r)) Source # 
Instance details

Defined in Control.Eff.Fresh

Associated Types

type StM (Eff (Fresh ': r)) a :: Type #

Methods

liftBaseWith :: (RunInBase (Eff (Fresh ': r)) m -> m a) -> Eff (Fresh ': r) a #

restoreM :: StM (Eff (Fresh ': r)) a -> Eff (Fresh ': r) a #

type StM (Eff (Fresh ': r)) a Source # 
Instance details

Defined in Control.Eff.Fresh

type StM (Eff (Fresh ': r)) a = StM (Eff r) (a, Int)

withFresh :: Monad m => a -> Int -> m (a, Int) Source #

Embed a pure value. Note that this is a specialized form of State's and we could have reused it.

fresh :: Member Fresh r => Eff r Int Source #

Produce a value that has not been previously produced.

runFresh' :: Int -> Eff (Fresh ': r) w -> Eff r w Source #

Run an effect requiring unique values.