explicit-sharing-0.5.0: Explicit Sharing of Monadic Effects

Stabilityexperimental
MaintainerSebastian Fischer <mailto:sebf@informatik.uni-kiel.de>

Control.Monad.Sharing

Contents

Description

This library provides an interface to monads that support explicit sharing. A project website with tutorials can be found at http://sebfisch.github.com/explicit-sharing.

Synopsis

Documentation

Classes

class Sharing m whereSource

Interface of monads that support explicit sharing.

Methods

share :: Shareable m a => m a -> m (m a)Source

Yields an action that returns the same results as the given action but whose effects are only executed once. Especially, when the resulting action is duplicated it returns the same result at every occurrence.

Instances

Monad m => Sharing (Lazy m) 
Monad m => Sharing (Lazy m) 

class Shareable m a whereSource

Interface of shareable nested monadic data types. The provided function shareArgs is supposed to map the given function on every monadic argument.

We provide instances of the Shareable class for some predefined Haskell types. For flat types the function shareArgs just returns its argument which has no arguments to which the given function could be applied.

Methods

shareArgs :: Monad n => (forall b. Shareable m b => m b -> n (m b)) -> a -> n aSource

Instances

Monad m => Shareable m Char 
Monad m => Shareable m Int 
Monad m => Shareable m Bool 
(Monad m, Shareable m a) => Shareable m [m a]

An instance for lists with monadic elements.

Monad m => Shareable m [Char] 
Monad m => Shareable m [Int] 
Monad m => Shareable m [Bool] 
(Monad m, Shareable m a) => Shareable m (List m a)

This instance allows to use nested monadic lists as argument to the Control.Monad.Sharing.share combinator.

class Convertible m a b whereSource

Interface for convertible datatypes. The provided function convArgs is supposed to map the given function on every argument of the given value and combine the results to give the converted value.

We provide instances of the Convertible class for some predefined Haskell types. For flat types the function convArgs just returns its argument which has no arguments to which the given function could be applied.

Methods

convArgs :: (forall c d. Convertible m c d => c -> m d) -> a -> m bSource

Instances

Monad m => Convertible m Char Char 
Monad m => Convertible m Int Int 
Monad m => Convertible m Bool Bool 
(Monad m, Convertible m a b) => Convertible m [m a] [b]

An instance to convert lists with monadic elements into ordinary lists.

(Monad m, Convertible m a b) => Convertible m [a] [m b]

An instance to convert ordinary lists into lists with monadic elements.

Monad m => Convertible m [Char] [Char] 
Monad m => Convertible m [Int] [Int] 
Monad m => Convertible m [Bool] [Bool] 
(Monad m, Convertible m a b) => Convertible m [a] (List m b)

This instance enables the function Control.Monad.Sharing.convert to transform ordinary Haskell lists into nested monadic lists.

(Monad m, Convertible m a b) => Convertible m (List m a) [b]

This instance enables the function Control.Monad.Sharing.convert to transform nested monadic lists into ordinary Haskell lists.

convert :: Convertible m a b => a -> m bSource

Converts a convertible value recursively.

Monad transformer

data Lazy m a Source

Continuation-based, store-passing implementation of explicit sharing. It is an inlined version of ContT (ReaderT Store m) where the result type of continuations is polymorphic.

Instances

MonadTrans Lazy 
Monad m => MonadState Store (Lazy m) 
Monad m => Monad (Lazy m) 
MonadPlus m => MonadPlus (Lazy m) 
MonadIO m => MonadIO (Lazy m) 
Monad m => Sharing (Lazy m) 

evalLazy :: (Monad m, Convertible (Lazy m) a b) => Lazy m a -> m bSource

Lifts all monadic effects to the top-level and unwraps the monad transformer for explicit sharing.