[Haskell-cafe] Alternative IO

Wolfgang Jeltsch g9ks157k at acme.softbase.org
Fri Jul 10 04:35:15 EDT 2009


Am Donnerstag, 9. Juli 2009 15:27 schrieb 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

Hello Cristiano,

I fear that this instance doesn’t satisfy required laws. As far as I know, the 
following equalities should hold:

    (*>) = (>>)

    f *> empty = empty

    empty <|> g = g

This implies the following:

    (f >> empty) <|> g = g

But this wouldn’t hold with your instance. (f >> empty) <|> g would cause the 
side effects of f and of g, while g would (obviously) only cause the side 
effects of g.

If empty would be a real empty, it would have to undo the effects of previous 
actions (like f above). So an Applicative instance makes sense for STM but 
not for IO.

Best wishes,
Wolfgang


More information about the Haskell-Cafe mailing list