[Haskell-cafe] RE: [Haskell] ANN control-monad-exception-0.1: Explicitly typed exceptions

Simon Peyton-Jones simonpj at microsoft.com
Mon Apr 27 04:14:08 EDT 2009


Is there a Haskell Wiki page on extensible exceptions?  The paper is a fine reference, it'd be cool to have a wiki page giving programmer-oriented guidance, saying
        what comes with GHC
        what other packages are available

and some simple examples of how to use them.

Simon

| -----Original Message-----
| From: haskell-bounces at haskell.org [mailto:haskell-bounces at haskell.org] On Behalf Of
| Pepe Iborra
| Sent: 25 April 2009 19:52
| To: haskell at haskell.org
| Subject: [Haskell] ANN control-monad-exception-0.1: Explicitly typed exceptions
|
| The control-monad-exception package [1] provides explicitly typed
| exceptions for Haskell.
| In other words, this is a perfect example of bundling in a Haskell
| library what for other
| programming languages is a native feature.
|
| The type of a computation in the EM monad carries a list of the exceptions that
| the computation may throw. A exception is raised with 'throw', which
| in addition adds it
| to the type, and captured with 'catch', which correspondingly removes
| it from the type.
| Only safe computations (all exceptions handled) can escape from the monad.
|
| The encoding used for the exception list is based on a phantom type
| variable carrying a
| @Throws@ constraint for every exception type. Catching an exception
| @e@ satifies the constraint
| @Throws e@ thus removing it from the type. It is possible to teach
| Throws about exception subtyping
| by manually inserting new instances declaring the subtyping relations
| between exceptions. I don't
| believe there is a better way to handle this, as the existential
| wrapper encoding used
| for Control.Exception.SomeException does not reveal the subtyping
| relations, but ideas are
| welcome.
|
| Example
| --------
| GHCi infers the following types
|
|  eval :: (Throws DivideByZero l, Throws SumOverflow l) => Expr -> EM l Double
|  eval `catch` \ (e::DivideByZero) -> return (-1)  :: Throws
| SumOverflow l => Expr -> EM l Double
|  runEM (eval `catch` \ (e::SomeException) -> return (-1))  :: Expr -> Double
|
| for the code below.
|
|
| > import Control.Monad.Exception
| > import Data.Typeable
|
| > data Expr = Add Expr Expr | Div Expr Expr | Val Double
| > eval (Val x)     = return x
| > eval (Add a1 a2) = do
| >    v1 <- eval a1
| >    v2 <- eval a2
| >    let sum = v1 + v2
| >    if sum < v1 || sum < v2 then throw SumOverflow else return sum
| > eval (Div a1 a2) = do
| >    v1 <- eval a1
| >    v2 <- eval a2
| >    if v2 == 0 then throw DivideByZero else return (v1 / v2)
|
| > data DivideByZero = DivideByZero deriving (Show, Typeable)
| > data SumOverflow  = SumOverflow  deriving (Show, Typeable)
|
| > instance Exception DivideByZero
| > instance Exception SumOverflow
|
|
| Comments and patches are welcome.
| Cheers,
| Pepe Iborra
|
| [1] - http://hackage.haskell.org/cgi-bin/hackage-scripts/package/control-monad-
| exception
| _______________________________________________
| Haskell mailing list
| Haskell at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell



More information about the Haskell-Cafe mailing list