
Hrmm. This should probably be made consistent with the MonadPlus instance for IO, so
empty = ioError (userError "mzero") Otherwse, I'm surprised this isn't already in the standard library.
I'd suggest submitting it to libraries@.
-Edward Kmett
On Thu, Jul 9, 2009 at 9:27 AM, Cristiano Paris
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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe