explicit-sharing-0.4.0.1: Explicit Sharing of Monadic Effects

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

Control.Monad.Sharing.Classes

Description

This library provides type classes for explicit sharing of monadic effects. Usually you don't need to import this library as it is reexported by the module Control.Monad.Sharing. You may want to do so, however, when writing your own implementation of explicit sharing.

Synopsis

Documentation

class Sharing m whereSource

Interface of monads that support explicit sharing.

Methods

share :: Trans m a 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) 

class Trans m a b whereSource

Interface to transform nested monadic data types. The provided function trans is supposed to map the given function on every monadic argument. The result of trans may be of the same type as the argument but can also be of a different type, e.g. to convert a value with nested monadic arguments to a corresponding value without.

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

Methods

trans :: (forall c d. Trans m c d => m c -> m (m d)) -> a -> m bSource

Instances

Monad m => Trans m Double Double 
Monad m => Trans m Float Float 
Monad m => Trans m Char Char 
Monad m => Trans m Int Int 
Monad m => Trans m Bool Bool 
(Monad m, Trans m a a) => Trans m [m a] [a]

An instance for lists with monadic elements that lifts all monadic effects to the top level and yields a list with non-monadic elements.

(Monad m, Trans m a a) => Trans m [m a] [m a]

An instance for lists with monadic elements.

Monad m => Trans m [Double] [Double] 
Monad m => Trans m [Float] [Float] 
Monad m => Trans m [Char] [Char] 
Monad m => Trans m [Int] [Int] 
Monad m => Trans m [Bool] [Bool] 
(Monad m, Trans m a b) => Trans m [a] (List m b)

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

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

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

(Monad m, Trans m a b) => Trans m (List m a) (List m b)

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

eval :: (Monad m, Trans m a b) => a -> m bSource

Lifts all monadic effects in nested monadic values to the top level. If m is a monad for non-determinism and the argument a data structure with nested non-determinism then the result corresponds to the normal form of the argument.