On 10-Jun-1998, Simon L Peyton Jones <[EMAIL PROTECTED]> wrote:
| 
| Alastair Reid has been very quiet, so I'll pipe up for him.

I was keeping quiet myself, because I am planning to write
a paper touching on this topic.  But the cat seems to be
mostly out of the bag now, so I might as well pipe up.
(Has Reid or anyone else published anything on this topic recently?)

| Here's a reasonable design for exceptions in Haskell:
...
| * raise :: String -> a
| * handle :: (String -> IO a) -> IO a -> IO a

You can do better than this.

In particular, `handle' need not be dependent on the IO monad.
You can use a seperate "nondetermistic set" monad for committed
choice nondeterminism.

>       module NDSet (
>               NDSet,
>               ndset_singleton, ndset_union, ndset_set_union, ndset_map,
>               ndset_throw, ndset_catch, ndset_handle, ndset_choose,
>               handle, throw,
>               unsafe_promise_singleton
>       ) where
>
>       -- type NDSet t
>       ndset_singleton :: t -> NDSet t
>       ndset_union :: NDSet t -> NDSet t -> NDSet t
>       ndset_set_union :: NDSet (NDSet t) -> NDSet t
>       ndset_map :: (t1 -> t2) -> NDSet t1 -> NDSet t2
>
>       instance Monad NDSet where
>               return = ndset_singleton
>               set >>= action = ndset_set_union (ndset_map action set)

The type `NDSet t' represents a set of values of type `t'.
However, the interface does not let you get at more than one
nondeterministically chosen element from the set, so the
implementation of the type only stores a single element.

This type is useful for committed choice nondeterminism in general,
and exceptions in particular:

>       type Exception = IOError        -- or String, etc.
>       data MaybeException t = OK t | GotException (NDSet Exception)
>       ndset_throw :: (NDSet Exception) -> any
>       ndset_catch :: t -> MaybeException t

This allows you to establish handlers in the
functional part of the code which does not have access to the IO monad.
Such code can catch exceptions, and then may at its option
ignore them, rethrow them, rethrow different exceptions,
store the exceptions in data structures (as values of type `NDSet Exception'),
and so forth.  However, you can't get at individual exceptions,
you can only apply functions to sets of exceptions.

Only once you get back to the IO monad can you select an individual exception:

>       ndset_choose :: IO (NDSet t) -> IO t

The `handle' and `throw' that you suggested can be implemented in terms
of these `ndset_throw', `ndset_catch', and `ndset_choose':

>       throw :: Exception -> any
>       throw e = ndset_throw (ndset_singleton e)
>
>       ndset_handle :: (Exception -> t) -> t -> NDSet t
>       ndset_handle handler value =
>               case (ndset_catch value) of
>                       OK value -> ndset_singleton value
>                       GotException exception_vals ->
>                               ndset_map handler exception_vals

>       handle :: (Exception -> IO a) -> IO a -> IO a
>       handle handler action = do
>            next_action <- ndset_choose (return (ndset_handle handler action))
>            next_action

In addition, the following primitive is very useful:

>       unsafe_promise_singleton :: NDSet t -> t
>       unsafe_promise_singleton s = unsafePerformIO (ndset_choose (return s))

The idea of this primitive is that the user is promising that the NDSet
in question is a singleton set; they can then get back the single
element.  This primitive is unsafe in general, but it can be used in
ways that are guaranteed to be safe.  For example, if only care about
whether you got an exception, not about what exception you got, you can
use the following:

>       -- `simple_handle x' returns `Nothing', if evaluation of `x' throws
>       -- an exception, or `Just x' otherwise.
>       simple_handle :: a -> Maybe a
>       simple_handle x = unsafe_promise_singleton (
>               ndset_handle (\ exception -> Nothing) (Just x))

Because we map all exceptions to `Nothing', and because a function
is guaranteed to either return a set of exceptions or return a value,
but not both, the set of values returned from the call to `ndset_handle'
is guaranteed to be either { Nothing } or { Just x }, and in either
case this is a singleton set, so it's safe to call `unsafe_promise_singleton'.

This is not a good example, because you can get the same effect more
simply using `ndset_catch' instead of `ndset_handle'.  Offhand,
I couldn't think of any good examples of its use with exceptions. 
However, `unsafe_promise_singleton' is definitely useful when NDSets
for things other than exceptions.

The implementation of most of this is quite straightforward:

>       newtype NDSet s = MakeNDSet s
>
>       ndset_singleton x = MakeNDSet x
>       ndset_union x y = x
>       ndset_set_union (MakeNDSet x) = x
>       ndset_map f (MakeNDSet x) = MakeNDSet (f x)
>
>       ndset_choose ndaction = do
>               MakeNDSet x <- ndaction
>               return x
>
>       instance Show s => Show (NDSet s) where
>               showsPrec p (MakeNDSet x) =
>                       showString ("{ " ++ show x ++ ", ... }")

However, you may need to prevent the compiler from optimizing
across the boundaries of this interface.
And of course the `ndset_throw' and `ndset_catch' primitives would
probably need to be implemented at a lower level.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]        |     -- the last words of T. S. Garp.


Reply via email to