[Haskell-cafe] A program which never crashes (even when a function calls "error")

J. Garrett Morris trevion at gmail.com
Tue Aug 1 03:22:03 EDT 2006


On 8/1/06, Stephane Bortzmeyer <bortzmeyer at nic.fr> wrote:
> How to do it in Haskell? How can I call functions like Prelude.head
> while being sure my program won't stop, even if I call head on an
> empty list (thus calling "error")?

Try looking at Control.Exception.  For example:

> module Test where

> import Control.Exception
> import Prelude hiding (catch)

> example =
>   (do print (head (tail "a"))
>       return "ok")
>   `catch` (\e -> do putStrLn ("Caught exception: " ++ show e)
>                     return "error")

produces:

*Test> z <- example
Caught exception: Prelude.head: empty list
*Test> z
"error"

This might be the beginning of what you want.

 /g


More information about the Haskell-Cafe mailing list