
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

To be honest -- that seems rather nice. Can has in Hackage? Bob On 9 Jul 2009, at 15:27, Cristiano Paris wrote:
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

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

On Thu, 9 Jul 2009, Cristiano Paris wrote:
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?
I just say, what I always say. :-) 'error' denotes a programming error and "catching" it is a hack, sometimes needed but less often than you think. For exceptions one must use 'throw'. Thus, you may e.g. define empty = throw ...

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

On Fri, Jul 10, 2009 at 10:35 AM, Wolfgang
Jeltsch
... 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.
Thanks. That's an argument :) -- Cristiano

On Jul 10, 2009, at 4:35 AM, Wolfgang Jeltsch wrote:
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.
I think the third equality you provide is too strong (which isn't to say that it might not be the law that people have documented and expect). Lots of useful alternative instances fail it, not least any parser combinator library (such as Parsec) without automatic backtracking. A more realistic law would perhaps be:
(f *> empty) <|> g = f *> g
Additionally, the second equality you provide is just wrong. f *> empty = empty is no more true than f *> g = g, which is no more true than f >> g = g, which is obviously not true at all, as putStrLn "Hey There" >> return () obviously /= return () Cheers, Sterl

Am Freitag, 10. Juli 2009 23:41 schrieben Sie:
On Jul 10, 2009, at 4:35 AM, Wolfgang Jeltsch wrote:
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.
I think the third equality you provide is too strong (which isn't to say that it might not be the law that people have documented and expect). Lots of useful alternative instances fail it, not least any parser combinator library (such as Parsec) without automatic backtracking.
Really? The third equality is required since Alternative instances have to be monoids with empty as the neutral element and (<|>) as composition.
[…]
Additionally, the second equality you provide is just wrong.
f *> empty = empty is no more true than f *> g = g,
I don’t understand this. The equation f *> g = g is much more general than f *> empty = empty. (<|>) usually denotes non-determinism and empty should be the neutral element of non-determinism, which is failing. This leads me to f *> empty = empty.
[…]
Best wishes, Wolfgang

On Fri, Jul 17, 2009 at 10:21 AM, Wolfgang
Jeltsch
Am Freitag, 10. Juli 2009 23:41 schrieben Sie:
Additionally, the second equality you provide is just wrong.
f *> empty = empty is no more true than f *> g = g,
I don’t understand this. The equation f *> g = g is much more general than f *> empty = empty. (<|>) usually denotes non-determinism and empty should be the neutral element of non-determinism, which is failing. This leads me to f *> empty = empty.
That's too strong, unless you want to restrict Alternative to
applicative functors with reversible side-effects.
It's generally accepted that LogicT IO is an instance of MonadPlus, but
liftIO (putStrLn "effects!") >> mzero /= mzero
I would expect LogicT IO to be an instance of Alternative as well.
--
Dave Menendez

On Friday 10 July 2009 4:35:15 am Wolfgang Jeltsch wrote:
I fear that this instance doesn’t satisfy required laws. As far as I know, the following equalities should hold:
(*>) = (>>)
f *> empty = empty
IO already fails at this law, because (f *> empty) is not the same as empty, it is a failing computation with the side effects of f. empty is only a left- zero in the IO monad.
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.
Of course, this can be seen as a different symptom of the same underlying problem (although if the initial equation for empty held, it'd work). There's been talk before of splitting MonadPlus into multiple classes for choice, which pick and choose which of these sorts of laws apply to each particular class. MonadPlus vs. MonadOrElse is one splitting, for instance, but I can't recall if IO would satisfy all the laws for either.* -- Dan * For instance, you might expect MonadOrElse to satisfy: f <|> g = f OR f <|> g = g but IO will only satisfy: f <|> g = f OR f <|> g = g-with-side-effects-from-f

Am Samstag, 11. Juli 2009 00:16 schrieben Sie:
On Friday 10 July 2009 4:35:15 am Wolfgang Jeltsch wrote:
I fear that this instance doesn’t satisfy required laws. As far as I know, the following equalities should hold:
(*>) = (>>)
f *> empty = empty
IO already fails at this law, because (f *> empty) is not the same as empty,
Huh? There was no Applicative instance for IO. This was the reason for Cristiano to define one, and my mail pointed out a problem in his definition. Best wishes, Wolfgang
participants (9)
-
Cristiano Paris
-
Cristiano Paris
-
Dan Doel
-
David Menendez
-
Edward Kmett
-
Henning Thielemann
-
Sterling Clover
-
Thomas Davie
-
Wolfgang Jeltsch