[Haskell-cafe] Alternative IO

Cristiano Paris cristiano.paris at gmail.com
Thu Jul 9 09:27:57 EDT 2009


As a joke, I wrote an instance of Alternative for IO actions:
{-# LANGUAGE ScopedTypeVariables #-}
module Main where

import Control.Applicative
import Control.Exception

instance Alternative IO where
  empty = undefined
  x <|> y = handle (\ (_ :: SomeException) -> y) x

This would allow to write IO code which failsafes to a value if the previous
computation failed, i.e.:

*Main Control.Applicative> undefined <|> print "Hello"
"Hello"
*Main Control.Applicative> print "Hello" <|> undefined
"Hello"

It seems a neat way to catch exception in some scenarios. What do you think?
Why is not Alternative IO defined in Control.Applicative?

Thanks,

Cristiano
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090709/b4f0145f/attachment.html


More information about the Haskell-Cafe mailing list