On Fri, Jul 17, 2009 at 10:21 AM, Wolfgang
Jeltsch wrote:
> 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 ge
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 f
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 <|>
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,
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 th
On Fri, Jul 10, 2009 at 10:35 AM, Wolfgang
Jeltsch wrote:
> ...
> 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 followin
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
>
On Thu, Jul 9, 2009 at 3:42 PM, Edward Kmett wrote:
> Hrmm. This should probably be made consistent with the MonadPlus instance
> for IO, so
>
> > empty = ioError (userError "mzero")
>
I agree. Of course, that was only a first attempt :)
Cristiano
___
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 (\ (_ :: Som
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 librar...@.
-Edward Kmett
On Thu, Jul 9, 2009 at 9:27 AM, Cristiano Paris
wr
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
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
12 matches
Mail list logo