explicit-sharing-0.9: 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 MonadPlus s => Sharing s whereSource

Interface of monads that support explicit sharing.

Methods

share :: Shareable s a => s a -> s (s 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

Nondet n => Sharing (Lazy n) 

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 Double 
Monad m => Shareable m Float 
Monad m => Shareable m Integer 
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 [Double] 
Monad m => Shareable m [Float] 
Monad m => Shareable m [Integer] 
Monad m => Shareable m [Int] 
Monad m => Shareable m [Bool] 
Monad m => Shareable m (a -> b) 
(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

convert :: a -> m bSource

Instances

Monad m => Convertible m Char Char 
Monad m => Convertible m Double Double 
Monad m => Convertible m Float Float 
Monad m => Convertible m Integer Integer 
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 [Double] [Double] 
Monad m => Convertible m [Float] [Float] 
Monad m => Convertible m [Integer] [Integer] 
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.

class Nondet n whereSource

Methods

failure :: nSource

(?) :: n -> n -> nSource

Instances

Nondet Bool 
Ord a => Nondet (Set a) 
Nondet (UnsafeResults a) 
Ord a => Nondet (Map a Rational) 

type MInt m = IntSource

type MChar m = CharSource

type MBool m = BoolSource