I want to thank Peter and Ralph for their explanation of how to use Monads
and Either.  

I have created a new version of the exception module that is syntactically
cleaner and supports mixing exception types.

It might have been nicer to do this with Existential types (I just read
about them today), but they do not add all that much because I use the
type information to pass the functional equivalent of a Java stack
trace.

Please tell me if the operators make sens or whether these operators are
in use elsewhere.

As a matter of course I think that some exception handling functionality
should go into the prelude because multiple different exception handling
systems will get messy as people share code.

-Alex- 
___________________________________________________________________
S. Alexander Jacobson                   i2x Media  
1-212-697-0184 voice                    1-212-697-1427 fax

I will go through different exception handling patterns and discuss how to
implement them with these new combinators.  Then I will discuss
implementation.  

Suppose we want to use a function which either returns a value or throws
exceptions of some type e.g.
----

> data FooExceptions a = InfiniteBlahException a a | SomeOtherException |
>                        DivisionByZeroException a

> foo x y | x==y   = throw $ InfiniteBlahException x y
>         | y==0   = throw $ DivisionByZeroException x
>         | x==0   = throw SomeOtherException
>         | True   = return $ x/y + log x + log (x-y)

-------

I. Simple function calling
Now we call this function using a system like this:

> oneType x y = res ++= handle
>  where 
>    res= show <<$ addThree << (return 1.0) <<= 
>                              (foo x y) <<= 
>                              (foo (x y)
>    addThree x y z = x + y + z
>    handle (InfiniteBlahException x y) = return  "Your x arg was bad"
>    handle (SomeOtherException) = return "live with it"

++= means return the result or handle the exception with the a function
<< means apply this function if we have a result or throw exception 
        For you monad folk: (\x \f -> >>+ return.f)
<<$ is the same as $ but in the exception handling case
<<= is partial application in the exceptions context

So here we have an example where an expression propogates a single
exception type and it is handled sanely.

II. Handling two different exception types:

> data LooExceptions = LooException
> loo x | x==0 = throw LooException
>       | True = return x

> multiType1 x y = res ++= handle
>  where 
>    res= show <<$ addThree << (return 1.0) <<= 
>                              (loo x) <<+ 
>                              (foo (x+1) y)
>    addThree x y z = x + y + z
>    handle (Right (InfiniteBlahException x y)) = return  "Your x arg was bad"
>    handle (Right (SomeOtherException)) = return "live with it"
>    handle (Left LooException) = return "you LOOse!"

We are using a new operator <<+ which basically says that we return a
value or either an exception of the type on the left or an exception of
the type on the right.  We can use Left/Right to build the functional
equivalent of an exception stack trace.

III Handling classes (here is where existential types wouldbe nice)

Suppose that the creators of th various exception types also provided
functions to use with them.  Then we want to take each class and pass it
to the right handler.

> multiType2 x y = res ++= handle 
>  where 
>    res= show <<$ addThree << (return 1.0) <<= (loo x)  <<+ (foo (x+1) y)
>    addThree x y z = x + y + z
>    handle (Left x) = handleLoo x
>    handle (Right x) = handleFoo x

These might be from the Foo package or the Loo package

> handleFoo (InfiniteBlahException x y) = return  "Your x arg was bad"
> handleFoo SomeOtherException = return "live with it"
> handleLoo LooException = return "you LOOse!"

IV Inserting exception handling inside an expression

There are many cases where we want to handle an exception side the context
of evaluation rather than pop out of our evaluating expression entirely.
Note that the internal exception handlers have to return an appropriate
type.

> multiType3 x y = res 
>  where 
>    res= show <<$ addThree << (return 1.0) <<= (loo x) ++=handleLoo
>               <<+ (foo (x+1) y) ++=handleFoo
>    addThree x y z = x + y + z
>    handleFoo (InfiniteBlahException x y) = return  4.5
>    handleFoo SomeOtherException = return 2.4
>    handleLoo LooException = return 5.0

V Exception renaming

It is common that a function renames and regroups exceptions that it
recieves in terms of semantics the caller will better understand.

> data LocalException = Stupid | Dumb

> multiType3 x y = res ++= handleLocal
>  where 
>    res= show <<$ addThree << (return 1.0) <<= 
>                              (loo x) ++= handleLoo <<=
>                              (foo (x+1) y) ++= handleFoo 
>    addThree x y z = x + y + z
>    handleFoo (InfiniteBlahException x y) = throw Stupid
>    handleFoo SomeOtherException = return 2.4
>    handleLoo LooException = throw Dumb
>    handleLocal Stupid = return "blah"
>    handleLocal Dumb = return "dumb"

The only problem here is that, for reasons I haven't figured out yet,
handleLocal is being inferred to return RetVal (Either b c) String,
rather than RetVal LocalException String.  If anyone can figure out why,
please tell me.

---------
Here is the actual code:

> module Exception (
>        (<<=),(<<+),(++=),(<<),(<<$),(++==),throw,ecatch,RetVal
> )
> where

> infixl 3 <<=,<<+
> infixl 7 ++=
> infixl 3 <<,++==
> infixr 1 <<$

> data RetVal b a = Result a | Exception b | ExceptionZero

> throw a = Exception a

> instance Monad (RetVal b) where
>  Exception x >>= f = Exception x
>  Result x >>= f = f x
>  return = Result

> instance Monad (Either b) where
>  Left a >>= k = Left a
>  Right a >>=k = k a
>  return = Right

> instance MonadZero (RetVal b) where
>  zero = ExceptionZero

> instance MonadPlus (RetVal b) where
>  Result x ++ y = Result x
>  Exception b ++ y = y
>  ExceptionZero ++ y = y


-------------------------------------------
--operators that make these things usable
-------------------------------------------

>--apply a function result or return an exception
> f << x =  x >>= return.f

>--same as above w/ RetVal Functions 
> (<<=) :: RetVal e (a->b) -> RetVal e a -> RetVal e b
> (Result f) <<= x = f<<x
> (Exception e) <<= _ = Exception e

> --handle two different exception classes being returned
> (<<+) :: RetVal a (b->c) -> RetVal d b -> RetVal (Either a d) c
> Exception e <<+ x = Exception (Left e)
> x <<+ (Exception e) = Exception (Right e)
> (Result f) <<+ (Result x) = (Result f) <<= (Result x) 

> --function composition, equivalent to f $ g
> f <<$ g = f << g 


-----------------------------
-----handler syntax----------
-----------------------------

> -- use ++= has higher precedence than <<+ and ++== to allow complex
handling
> --when you want to return a RetVal
> (++=) :: RetVal a b -> (a->RetVal c b) -> RetVal c b
> (Result x) ++= h = (Result x)
> (Exception f) ++= h = h f

> --when you want to return the underlying result
> (Result x) ++== handler = x
> (Exception x) ++== handler = handler x
> ecatch r handler = r ++== handler





Reply via email to