{-# LANGUAGE PackageImports #-}
import "mtl" Control.Monad.Trans
import Data.Monadic.List
This literate program explains how to use the explicit-sharing package which provides the following module.
import Control.Monad.Sharing
The interface of this module basically consists of two type classes. Instances of Sharing
support a combinator share
for explicit sharing and are usually monads. If you feel like you don't know enough about monads you may want to look at the Typeclassopedia.
class Sharing m
where
share :: Shareable m a => m a -> m (m a)
The type class Shareable
is an interface to data that can be shared explicitly.
The function share
takes a monadic action of type m a
and yields an action in the same monad which yields a monadic action of the same type as the argument. The idea is that share
yields something like the original action which can be duplicated without duplicating the effects.
Let's look at an example. First consider a program that does not use explicit sharing.
dup_get :: IO String
dup_get = do let get = getChar
x <- get
y <- get
z <- get
return [x,y,z]
This action renames the predefined action getChar
and calls it three times returning a list of the results of the three calls:
*Main> dup_get
abc
"abc"
Each occurrence of get
reads a different character from standard input, i.e., has its own independent input effect and all occurrences of get
can have different results. Haskells let
construct shares the IO action getChar
which can still be executed independently more than once.
The share
combinator provides a different kind of sharing. An IO action that is shared explicitly using share
can still be executed multiple times but its effects are only performed on first execution and an explicitly shared action will return the same result whenever it is executed.
Here is a variant of the above action with explicit sharing.
dup_shared_get :: (MonadIO m, Sharing m) => m String
dup_shared_get = do get <- share (liftIO getChar)
x <- get
y <- get
z <- get
return [x,y,z]
Instead of the built-in let
construct this action uses the share
combinator to share the (now lifted) getChar
action. We need to lift the getChar
action because we cannot execute dup_shared_get
directly in the IO monad which does not support the share
combinator.
We can run this action using the operation evalLazy
.
*Main> evalLazy dup_shared_get :: IO String
abc
"aaa"
This time, the result is "aaa"
rather than "abc"
. The shared get
action only performs the effects of getChar
once and yields the result of the first execution at each duplicated occurrence. The remaining characters ("bc"
in the example call above) are never read.
This behaviour may seem as if share
simply executes the given action and returns an action that yields the obtained result. It does not. The action given to share
is only executed if the action that share
returns is, i.e., share
is lazy:
ignore_shared :: (MonadIO m, Sharing m) => m String
ignore_shared =
do action <- share (liftIO (error "don't touch me!" :: IO String))
return "didn't touch you."
Running ignore_shared
yields "didn't touch you."
without touching the error
call:
*Main> evalLazy ignore_shared :: IO String
"didn't touch you."
Let's return to the type class Shareable
that specifies what data can be shared. The share
combinator is not only applicable to predefined Haskell types like String
but also to user-defined types that contain nested monadic components. For example, the module Data.Monadic.List
defines a type for lists with monadic heads and tails.
data List m a = Nil | Cons (m a) (m (List m a))
In order to be able to use share
with values of this type, we need an instance of Shareable
(which is also provided out of the box).
instance (Monad m, Shareable m a) => Shareable m (List m a)
where
shareArgs _ Nil = return Nil
shareArgs f (Cons x xs) = return Cons `ap` f x `ap` f xs
The type class Shareable
defines one operation shareArgs
to generically traverse nested monadic types. As you can see in the above instance declaration, the given function f
is applied to every monadic child of a compound value and the results are combined using the matched constructor.
The share
combinator uses this functionality to share nested monadic components of data recursively. Here is an example that shares an infinite List
of getChar
operations and returns a list of some of them that are duplicated.
share_list :: (MonadIO m, Sharing m) => m (List m Char)
share_list = do gets <- share getChars
Cons x xs <- gets
Cons y ys <- xs
Cons z zs <- gets
cons x (cons y (cons z (cons x (cons y (cons z nil)))))
where
getChars = cons (liftIO getChar) getChars
The functions nil
and cons
are helper functions to construct nested monadic lists. This example is definitely contrived but it helps to make a point: the infine list gets
is shared and all contained actions are shared too. Hence, x
and xs
are the same as z
and zs
and all actions yield the same results when duplicated. The result of share_list
is a list with six elements that will read two characters from the standard input when executed.
How can we observe this list? The List
type comes with an instance of another type class Convertible
that allows evalLazy
to convert List
s to ordinary Haskell lists.
instance (Monad m, Convertible m a b) => Convertible m (List m a) [b]
where
convArgs _ Nil = return []
convArgs f (Cons x xs) = return (:) `ap` (x >>= f) `ap` (xs >>= f)
This instance lifts all nested monadic effects to the top-level such that a corresponding transformation yields an ordinary list without any nested effects.
Now we can observe that indeed only two characters are read:
*Main> evalLazy share_list :: IO String
abc
"abaaba"
In order to convert in the other direction, there is yet another instance of Convertible
for List
s:
instance (Monad m, Convertible m a b) => Convertible m [a] (List m b)
where
convArgs _ [] = return Nil
convArgs f (x:xs) = return (Cons (f x) (f xs))
Thanks to this instance, we can use the function
convert :: Convertible m a b => a -> m b
to convert a list of type [Char]
into one of type m (List m Char)
.
Now, we have seen it all: the share
combinator from the type class Sharing
which implements explicit sharing of monadic effects such that monadic actions can be duplicated without duplicating their effects and three different instances of the type classes Shareable
and Convertible
which allow nested monadic data to be shared and converted back and forth to ordinary data respectively. But what is this good for?
A monadic effect whose interaction whith sharing is particularly interesting ins non-determinism. By combining the features for non-determinism provided by the MonadPlus
type class with explicit sharing provided by the Sharing
class we can implement lazy functional logic programming as advocated, e.g., by the Curry language in pure Haskell.
How to translate Curry programs to Haskell using explicit sharing is worth a different tutorial.