[Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Gregory Crosswhite
Today I learned (tldr; TIL) that the "fail" in the Monad class was added
as a hack to deal with the consequences of the decision to remove
"unfailable" patterns from the language.  I will attempt to describe the
story as I have picked it up from reading around, but please feel free
to correct me on the details.  :-)

An "unfailable" pattern (which is a generalization of an "irrefutable"
pattern) is a pattern which can never fail (excluding the possibility of
_|_), such as

let (x,y) = pair

Before "fail" was a method of the Monad class, using refutable patterns
in a monad required the type to be an instance of MonadZero (that is,
MonadPlus without the plus), so that for example

do Just x <- m

required that the monad be an instance of MonadZero.  If you avoided
such patterns, your Monad did not have to have this instance, so that
for example

do (x,y) <- pair

would not require MonadZero because the pattern is unfailable.

To me this seems like a lovely way of handling the whole matter, and
much improved over the incredibly ugly wart of having a "fail" method in
the Monad class.  In fact, I think I remember people on this list and in
other forums occasionally bringing something like this approach up as a
way of getting rid of the "fail" wart.

So my question is, why did we go to all of the trouble to transition
away from the MonadZero approach to the current system to begin with? 
What was so bad about "unfailable" patterns that it was decided to
remove them and in doing so replace MonadZero with a mandatory "fail"
method in Monad?  I mean, this *is* Haskell, so my safest assumption is
that smart people were involved in making this decision and therefore
the reasons much have been really good (or at least, seemed good given
the information at the time).  :-)

Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Edward Z. Yang
Hello Gregory,

The original (1998!) conversation can be found here:

http://www.mail-archive.com/haskell@haskell.org/msg03002.html

I think Simon Peyton-Jones' example really sums up the whole issue:

But [MonadZero] really sticks in my craw.  How can we explain this:

f :: Monad m => m (a,b) -> m a
f m1 = do { x <- m1; return (fst x) }

g :: MonadZero m => m (a,b) -> m a
g m1 = do { (a,b) <- m1; return a }

h :: Monad m => m (a,b) -> m a
h m1 = do { ~(a,b) <- m1; return a }

Why must g be in MonadZero?  Because the pattern (a,b) is refutable (by
bottom).

In my opinion, the /flexibility/ that was added by mfail was the real
mistake; we should have just had incomplete <- matches be handled the same
way ordinary incomplete pattern matches were accomodated, and figured out
how to nicely allow for multiple patterns in do-notation.  In other words,
MonadZero has no place in dealing with pattern match failure!

But this ship has long sailed.

Cheers,
Edward

Excerpts from Gregory Crosswhite's message of Thu Jan 19 21:47:42 -0500 2012:
> Today I learned (tldr; TIL) that the "fail" in the Monad class was added
> as a hack to deal with the consequences of the decision to remove
> "unfailable" patterns from the language.  I will attempt to describe the
> story as I have picked it up from reading around, but please feel free
> to correct me on the details.  :-)
> 
> An "unfailable" pattern (which is a generalization of an "irrefutable"
> pattern) is a pattern which can never fail (excluding the possibility of
> _|_), such as
> 
> let (x,y) = pair
> 
> Before "fail" was a method of the Monad class, using refutable patterns
> in a monad required the type to be an instance of MonadZero (that is,
> MonadPlus without the plus), so that for example
> 
> do Just x <- m
> 
> required that the monad be an instance of MonadZero.  If you avoided
> such patterns, your Monad did not have to have this instance, so that
> for example
> 
> do (x,y) <- pair
> 
> would not require MonadZero because the pattern is unfailable.
> 
> To me this seems like a lovely way of handling the whole matter, and
> much improved over the incredibly ugly wart of having a "fail" method in
> the Monad class.  In fact, I think I remember people on this list and in
> other forums occasionally bringing something like this approach up as a
> way of getting rid of the "fail" wart.
> 
> So my question is, why did we go to all of the trouble to transition
> away from the MonadZero approach to the current system to begin with? 
> What was so bad about "unfailable" patterns that it was decided to
> remove them and in doing so replace MonadZero with a mandatory "fail"
> method in Monad?  I mean, this *is* Haskell, so my safest assumption is
> that smart people were involved in making this decision and therefore
> the reasons much have been really good (or at least, seemed good given
> the information at the time).  :-)
> 
> Cheers,
> Greg
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Edward Z. Yang
Oh, I'm sorry! On a closer reading of your message, you're asking not
only asking why 'fail' was added to Monad, but why unfailable patterns
were removed.

Well, from the message linked:

In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
(it can't fail to match).  But the Haskell 1.4 story is unattractive becuase
a) we have to introduce the (new) concept of unfailable
b) if you add an extra constructor to a single-constructor type
   then pattern matches on the original constructor suddenly become
   failable

(b) is a real killer: suppose that you want to add a new constructor and
fix all of the places where you assumed there was only one constructor.
The compiler needs to emit warnings in this case, and not silently transform
these into failable patterns handled by MonadZero...

Edward

Excerpts from Gregory Crosswhite's message of Thu Jan 19 21:47:42 -0500 2012:
> Today I learned (tldr; TIL) that the "fail" in the Monad class was added
> as a hack to deal with the consequences of the decision to remove
> "unfailable" patterns from the language.  I will attempt to describe the
> story as I have picked it up from reading around, but please feel free
> to correct me on the details.  :-)
> 
> An "unfailable" pattern (which is a generalization of an "irrefutable"
> pattern) is a pattern which can never fail (excluding the possibility of
> _|_), such as
> 
> let (x,y) = pair
> 
> Before "fail" was a method of the Monad class, using refutable patterns
> in a monad required the type to be an instance of MonadZero (that is,
> MonadPlus without the plus), so that for example
> 
> do Just x <- m
> 
> required that the monad be an instance of MonadZero.  If you avoided
> such patterns, your Monad did not have to have this instance, so that
> for example
> 
> do (x,y) <- pair
> 
> would not require MonadZero because the pattern is unfailable.
> 
> To me this seems like a lovely way of handling the whole matter, and
> much improved over the incredibly ugly wart of having a "fail" method in
> the Monad class.  In fact, I think I remember people on this list and in
> other forums occasionally bringing something like this approach up as a
> way of getting rid of the "fail" wart.
> 
> So my question is, why did we go to all of the trouble to transition
> away from the MonadZero approach to the current system to begin with? 
> What was so bad about "unfailable" patterns that it was decided to
> remove them and in doing so replace MonadZero with a mandatory "fail"
> method in Monad?  I mean, this *is* Haskell, so my safest assumption is
> that smart people were involved in making this decision and therefore
> the reasons much have been really good (or at least, seemed good given
> the information at the time).  :-)
> 
> Cheers,
> Greg
> 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Gregory Crosswhite
On 01/20/12 13:23, Edward Z. Yang wrote:
> In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
> (it can't fail to match).  But the Haskell 1.4 story is unattractive 
> becuase
> a) we have to introduce the (new) concept of unfailable
> b) if you add an extra constructor to a single-constructor type
>then pattern matches on the original constructor suddenly 
> become
>failable
>
> (b) is a real killer: suppose that you want to add a new constructor and
> fix all of the places where you assumed there was only one constructor.
> The compiler needs to emit warnings in this case, and not silently transform
> these into failable patterns handled by MonadZero...

Okay, great, that explains two things that had not been clear to me: 
first, that the notion of "unfailable" was not removed from the language
so much as not added in the first place, and second, that if
"unfailable" *had* been added to the language then this would have
created the serious risk that adding a new constructor to a type could
change the meaning of your code by changing formerly irrefutable pattern
matches into potential sources of mzeros.

Thanks!
Greg


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Dan Doel
On Thu, Jan 19, 2012 at 10:43 PM, Gregory Crosswhite
 wrote:
> first, that the notion of "unfailable" was not removed from the language
> so much as not added in the first place

No, this is not correct. Unfailable patterns were specified in Haskell
1.4 (or, they were called "failure-free" there; they likely existed
earlier, too, but I'll leave the research to people who are
interested). They were "new" in the sense that they were introduced
only for the purposes of desugaring do/comprehensions, whereas
refutable vs. irrefutable patterns need to be talked about for other
purposes.

-- Dan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Michael Snoyman
On Fri, Jan 20, 2012 at 5:23 AM, Edward Z. Yang  wrote:
> Oh, I'm sorry! On a closer reading of your message, you're asking not
> only asking why 'fail' was added to Monad, but why unfailable patterns
> were removed.
>
> Well, from the message linked:
>
>    In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
>    (it can't fail to match).  But the Haskell 1.4 story is unattractive 
> becuase
>            a) we have to introduce the (new) concept of unfailable
>            b) if you add an extra constructor to a single-constructor type
>               then pattern matches on the original constructor suddenly become
>               failable
>
> (b) is a real killer: suppose that you want to add a new constructor and
> fix all of the places where you assumed there was only one constructor.
> The compiler needs to emit warnings in this case, and not silently transform
> these into failable patterns handled by MonadZero...

But wait a second... this is exactly the situation we have today!
Suppose I write some code:

data MyType = Foo

test myType = do
Foo <- myType
return ()

As expected, no warnings. But if I change this "unfailable" code above
to the following failable version:

data MyType = Foo | Bar

test myType = do
Foo <- myType
return ()

I *still* get no warnings! We didn't make sure the compiler spits out
warnings. Instead, we guaranteed that it *never* will. This has
actually been something that bothers me a lot. Whereas everywhere else
in my pattern matching code, the compiler can make sure I didn't make
some stupid mistake, in do-notation I can suddenly get a runtime
error.

My opinion is we should either reinstate the MonadZero constraint, or
simply can failable pattern matches.

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Edward Z. Yang
Aw, that is really suboptimal.  Have you filed a bug?

Edward

Excerpts from Michael Snoyman's message of Thu Jan 19 23:29:59 -0500 2012:
> On Fri, Jan 20, 2012 at 5:23 AM, Edward Z. Yang  wrote:
> > Oh, I'm sorry! On a closer reading of your message, you're asking not
> > only asking why 'fail' was added to Monad, but why unfailable patterns
> > were removed.
> >
> > Well, from the message linked:
> >
> >    In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
> >    (it can't fail to match).  But the Haskell 1.4 story is unattractive 
> > becuase
> >            a) we have to introduce the (new) concept of unfailable
> >            b) if you add an extra constructor to a single-constructor type
> >               then pattern matches on the original constructor suddenly 
> > become
> >               failable
> >
> > (b) is a real killer: suppose that you want to add a new constructor and
> > fix all of the places where you assumed there was only one constructor.
> > The compiler needs to emit warnings in this case, and not silently transform
> > these into failable patterns handled by MonadZero...
> 
> But wait a second... this is exactly the situation we have today!
> Suppose I write some code:
> 
> data MyType = Foo
> 
> test myType = do
> Foo <- myType
> return ()
> 
> As expected, no warnings. But if I change this "unfailable" code above
> to the following failable version:
> 
> data MyType = Foo | Bar
> 
> test myType = do
> Foo <- myType
> return ()
> 
> I *still* get no warnings! We didn't make sure the compiler spits out
> warnings. Instead, we guaranteed that it *never* will. This has
> actually been something that bothers me a lot. Whereas everywhere else
> in my pattern matching code, the compiler can make sure I didn't make
> some stupid mistake, in do-notation I can suddenly get a runtime
> error.
> 
> My opinion is we should either reinstate the MonadZero constraint, or
> simply can failable pattern matches.
> 
> Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Michael Snoyman
On Fri, Jan 20, 2012 at 6:41 AM, Edward Z. Yang  wrote:
> Aw, that is really suboptimal.  Have you filed a bug?

I think it's a feature, not a bug. When dealing with monads that
provide nice[1] implementations of `fail`, you can (ab)use this to
avoid writing a bunch of case expressions. I remember reading it in
one of the first tutorials on Haskell I looked at (four years ago now?
you can see how much this bothered me if I still remember that).

I admit that there are some use cases where the current behavior is
convenient, but I think we're paying too steep a price. If we got rid
of this feature entirely, we could (a) get rid of fail and (b) have
the compiler warn us about a bunch of errors at compile time.

But maybe I should file a feature request: provide an extra warning
flag (turned on by -Wall) that will warn when you match on a failable
pattern. Essentially, I would want:

SomeConstr args <- someAction

to be interpreted as:

temp <- someAction
case temp of
SomeConstr args ->

Michael

[1] For some people's definition of nice, not mine.

>
> Edward
>
> Excerpts from Michael Snoyman's message of Thu Jan 19 23:29:59 -0500 2012:
>> On Fri, Jan 20, 2012 at 5:23 AM, Edward Z. Yang  wrote:
>> > Oh, I'm sorry! On a closer reading of your message, you're asking not
>> > only asking why 'fail' was added to Monad, but why unfailable patterns
>> > were removed.
>> >
>> > Well, from the message linked:
>> >
>> >    In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
>> >    (it can't fail to match).  But the Haskell 1.4 story is unattractive 
>> > becuase
>> >            a) we have to introduce the (new) concept of unfailable
>> >            b) if you add an extra constructor to a single-constructor type
>> >               then pattern matches on the original constructor suddenly 
>> > become
>> >               failable
>> >
>> > (b) is a real killer: suppose that you want to add a new constructor and
>> > fix all of the places where you assumed there was only one constructor.
>> > The compiler needs to emit warnings in this case, and not silently 
>> > transform
>> > these into failable patterns handled by MonadZero...
>>
>> But wait a second... this is exactly the situation we have today!
>> Suppose I write some code:
>>
>>     data MyType = Foo
>>
>>     test myType = do
>>         Foo <- myType
>>         return ()
>>
>> As expected, no warnings. But if I change this "unfailable" code above
>> to the following failable version:
>>
>>     data MyType = Foo | Bar
>>
>>     test myType = do
>>         Foo <- myType
>>         return ()
>>
>> I *still* get no warnings! We didn't make sure the compiler spits out
>> warnings. Instead, we guaranteed that it *never* will. This has
>> actually been something that bothers me a lot. Whereas everywhere else
>> in my pattern matching code, the compiler can make sure I didn't make
>> some stupid mistake, in do-notation I can suddenly get a runtime
>> error.
>>
>> My opinion is we should either reinstate the MonadZero constraint, or
>> simply can failable pattern matches.
>>
>> Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Edward Z. Yang
It's not obvious that this should be turned on by -Wall, since
you would also trigger errors on uses like:

[ x | Just x <- xs ]

T_T

But I do think it ought to be an option.

Cheers,
Edward

Excerpts from Michael Snoyman's message of Thu Jan 19 23:52:10 -0500 2012:
> On Fri, Jan 20, 2012 at 6:41 AM, Edward Z. Yang  wrote:
> > Aw, that is really suboptimal.  Have you filed a bug?
> 
> I think it's a feature, not a bug. When dealing with monads that
> provide nice[1] implementations of `fail`, you can (ab)use this to
> avoid writing a bunch of case expressions. I remember reading it in
> one of the first tutorials on Haskell I looked at (four years ago now?
> you can see how much this bothered me if I still remember that).
> 
> I admit that there are some use cases where the current behavior is
> convenient, but I think we're paying too steep a price. If we got rid
> of this feature entirely, we could (a) get rid of fail and (b) have
> the compiler warn us about a bunch of errors at compile time.
> 
> But maybe I should file a feature request: provide an extra warning
> flag (turned on by -Wall) that will warn when you match on a failable
> pattern. Essentially, I would want:
> 
> SomeConstr args <- someAction
> 
> to be interpreted as:
> 
> temp <- someAction
> case temp of
> SomeConstr args ->
> 
> Michael
> 
> [1] For some people's definition of nice, not mine.
> 
> >
> > Edward
> >
> > Excerpts from Michael Snoyman's message of Thu Jan 19 23:29:59 -0500 2012:
> >> On Fri, Jan 20, 2012 at 5:23 AM, Edward Z. Yang  wrote:
> >> > Oh, I'm sorry! On a closer reading of your message, you're asking not
> >> > only asking why 'fail' was added to Monad, but why unfailable patterns
> >> > were removed.
> >> >
> >> > Well, from the message linked:
> >> >
> >> >    In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
> >> >    (it can't fail to match).  But the Haskell 1.4 story is unattractive 
> >> > becuase
> >> >            a) we have to introduce the (new) concept of unfailable
> >> >            b) if you add an extra constructor to a single-constructor 
> >> > type
> >> >               then pattern matches on the original constructor suddenly 
> >> > become
> >> >               failable
> >> >
> >> > (b) is a real killer: suppose that you want to add a new constructor and
> >> > fix all of the places where you assumed there was only one constructor.
> >> > The compiler needs to emit warnings in this case, and not silently 
> >> > transform
> >> > these into failable patterns handled by MonadZero...
> >>
> >> But wait a second... this is exactly the situation we have today!
> >> Suppose I write some code:
> >>
> >>     data MyType = Foo
> >>
> >>     test myType = do
> >>         Foo <- myType
> >>         return ()
> >>
> >> As expected, no warnings. But if I change this "unfailable" code above
> >> to the following failable version:
> >>
> >>     data MyType = Foo | Bar
> >>
> >>     test myType = do
> >>         Foo <- myType
> >>         return ()
> >>
> >> I *still* get no warnings! We didn't make sure the compiler spits out
> >> warnings. Instead, we guaranteed that it *never* will. This has
> >> actually been something that bothers me a lot. Whereas everywhere else
> >> in my pattern matching code, the compiler can make sure I didn't make
> >> some stupid mistake, in do-notation I can suddenly get a runtime
> >> error.
> >>
> >> My opinion is we should either reinstate the MonadZero constraint, or
> >> simply can failable pattern matches.
> >>
> >> Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Evan Laforge
On Thu, Jan 19, 2012 at 8:53 PM, Edward Z. Yang  wrote:
> It's not obvious that this should be turned on by -Wall, since
> you would also trigger errors on uses like:
>
>    [ x | Just x <- xs ]

I was going to say, perhaps refutable matches were considered
important was because back then list and monad comprehensions were
still the same.  List-comps is the only place I use refutable matches,
but they're extremely handy.  I would have suggested that listcomp
match failures yield [] but monad ones be errors, but now that list
comps and monads are back together again maybe that's not so easy to
do...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread John Meacham
> As expected, no warnings. But if I change this "unfailable" code above
> to the following failable version:
>
>    data MyType = Foo | Bar
>
>    test myType = do
>        Foo <- myType
>        return ()
>
> I *still* get no warnings! We didn't make sure the compiler spits out
> warnings. Instead, we guaranteed that it *never* will.

This is actually the right useful behavior. using things like

do
   Just x <- xs
   Just y <- ys
   return (x,y)

will do the right thing, failing if xs or ysresults in Nothing. for
instance, in the list monad, it will create the cross product of the
non Nothing members of the two lists. a parse monad may backtrack and
try another route, the IO monad will create a useful (and
deterministic/catchable) exception pointing to the exact file and line
number of the pattern match. The do notation is the only place in
haskell that allows us to hook into the pattern matching mechanism of
the language in a general way.

John

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Michael Snoyman
On Jan 20, 2012 8:31 AM, "John Meacham"  wrote:
>
> > As expected, no warnings. But if I change this "unfailable" code above
> > to the following failable version:
> >
> >data MyType = Foo | Bar
> >
> >test myType = do
> >Foo <- myType
> >return ()
> >
> > I *still* get no warnings! We didn't make sure the compiler spits out
> > warnings. Instead, we guaranteed that it *never* will.
>
> This is actually the right useful behavior. using things like
>
> do
>   Just x <- xs
>   Just y <- ys
>   return (x,y)
>
> will do the right thing, failing if xs or ysresults in Nothing. for
> instance, in the list monad, it will create the cross product of the
> non Nothing members of the two lists. a parse monad may backtrack and
> try another route, the IO monad will create a useful (and
> deterministic/catchable) exception pointing to the exact file and line
> number of the pattern match. The do notation is the only place in
> haskell that allows us to hook into the pattern matching mechanism of
> the language in a general way.
>
>John

I mention later that this is a "feature, not a bug" to some people, but I'm
not one of them. The convenience of having this feature is IMO far
outweighed by the cost of the runtime errors it can produce if you use the
pattern matching in the wrong monad (e.g., IO, Reader, Writer...).

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Gregory Crosswhite
On 01/20/12 14:52, Michael Snoyman wrote:
> Essentially, I would want:
>
> SomeConstr args <- someAction
>
> to be interpreted as:
>
> temp <- someAction
> case temp of
> SomeConstr args ->

I completely agree;  perhaps what we really want though is something
more akin to a language extension --- say,
DisableMonadFailForRefutablePatterns?

Cheers,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Dan Doel
On Thu, Jan 19, 2012 at 11:11 PM, Dan Doel  wrote:
> No, this is not correct. Unfailable patterns were specified in Haskell
> 1.4 (or, they were called "failure-free" there; they likely existed
> earlier, too, but I'll leave the research to people who are
> interested). They were "new" in the sense that they were introduced
> only for the purposes of desugaring do/comprehensions, whereas
> refutable vs. irrefutable patterns need to be talked about for other
> purposes.

I should also note: GHC already implements certain unfailable patterns
the 1.4 way when using RebindableSyntax (possibly by accident):

{-# LANGUAGE RebindableSyntax, MonadComprehensions #-}

module Test where

import qualified Prelude
import Prelude (String, Maybe(..))

import Control.Applicative

class Applicative m => Monad m where
  (>>=) :: m a -> (a -> m b) -> m b

return :: Applicative f => a -> f a
return = pure

class Monad m => MonadZero m where
  mzero :: m a
  fail  :: String -> m a

  mzero = fail "mzero"
  fail _ = mzero

foo :: MonadZero m => m (Maybe a) -> m a
foo m = do Just x <- m
   pure x

bar :: Monad m => m (a, b) -> m a
bar m = do (x, y) <- m
   pure x

baz :: MonadZero m => m (Maybe a) -> m a
baz m = [ x | Just x <- m ]

quux :: Monad m => m (a, b) -> m a
quux m = [ x | (x, y) <- m ]

It doesn't work for types defined with data, but it works for built-in tuples.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-19 Thread Luminous Fennell
On Fri, Jan 20 2012 at 06:22 +0100, Evan Laforge wrote:

> On Thu, Jan 19, 2012 at 8:53 PM, Edward Z. Yang  wrote:
>> It's not obvious that this should be turned on by -Wall, since
>> you would also trigger errors on uses like:
>>
>>   [ x | Just x <- xs ]

> [...]
>  I would have suggested that listcomp
> match failures yield [] but monad ones be errors, but now that list
> comps and monads are back together again maybe that's not so easy to
> do...
>

Perhaps a generalization of this would be to warn only if fail was
inherited by the original Monad typeclass, where it seems obvious that
fail takes the role of a ``work-around''. When fail is overwritten one
could perhaps assume that calling it is the intended behavior for
pattern match failures.

Lu

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread James Cook
On Jan 20, 2012, at 1:40 AM, Michael Snoyman wrote:

> On Jan 20, 2012 8:31 AM, "John Meacham"  wrote:
> >
> > > As expected, no warnings. But if I change this "unfailable" code above
> > > to the following failable version:
> > >
> > >data MyType = Foo | Bar
> > >
> > >test myType = do
> > >Foo <- myType
> > >return ()
> > >
> > > I *still* get no warnings! We didn't make sure the compiler spits out
> > > warnings. Instead, we guaranteed that it *never* will.
> >
> > This is actually the right useful behavior. using things like
> >
> > do
> >   Just x <- xs
> >   Just y <- ys
> >   return (x,y)
> >
> > will do the right thing, failing if xs or ysresults in Nothing. for
> > instance, in the list monad, it will create the cross product of the
> > non Nothing members of the two lists. a parse monad may backtrack and
> > try another route, the IO monad will create a useful (and
> > deterministic/catchable) exception pointing to the exact file and line
> > number of the pattern match. The do notation is the only place in
> > haskell that allows us to hook into the pattern matching mechanism of
> > the language in a general way.
> >
> >John
> 
> I mention later that this is a "feature, not a bug" to some people, but I'm 
> not one of them. The convenience of having this feature is IMO far outweighed 
> by the cost of the runtime errors it can produce if you use the pattern 
> matching in the wrong monad (e.g., IO, Reader, Writer...).
> 
It seems like there must be deeper reasons than stated so far for wanting to 
remove the "failable" concept from the spec, because all the ones given so far 
seem more like pros than cons.

For example, those runtime errors would be type errors!  And when adding 
additional constructors to a single-constructor type, it would not silently 
change the meaning in most places - it would cause type errors in places where 
the binding no longer makes sense and "change the meaning" in a predictable way 
(the way it does now) in places where it does make sense.  The former sounds 
fantastic to me, and the latter sounds acceptable (but a warning for those who 
don't find it acceptable would be a good idea too).

There is of course still a risk that adding a constructor can cause silent 
misbehavior in code that uses those type of bindings in monads that _are_ 
instances of MonadZero, but personally the number of times I have been bitten 
by that or heard of anyone else actually being bitten by it (i.e., zero) is a 
lot smaller than the number of times I've decided a "failable" binding was just 
the right concise-and-clear way to implement a parser, filter, etc.  The only 
problem I have with that style is the fact that it is not rejected in places 
where it doesn't make sense.

-- James

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread James Cook
Actually, that's not what this conversation is about - it's about what to with 
those types of bindings instead of the way 1.4 had been doing it.

On Jan 19, 2012, at 10:19 PM, Edward Z. Yang wrote:

> Hello Gregory,
> 
> The original (1998!) conversation can be found here:
> 
>http://www.mail-archive.com/haskell@haskell.org/msg03002.html
> 
> I think Simon Peyton-Jones' example really sums up the whole issue:
> 
>But [MonadZero] really sticks in my craw.  How can we explain this:
> 


[MonadZero] is not the correct summary here.  "(1)" refers to the proposal of 
replacing the "failable" with "refutable" in the semantics, which leads to the 
weird example he then gives.


>f :: Monad m => m (a,b) -> m a
>f m1 = do { x <- m1; return (fst x) }
> 
>g :: MonadZero m => m (a,b) -> m a
>g m1 = do { (a,b) <- m1; return a }
> 
>h :: Monad m => m (a,b) -> m a
>h m1 = do { ~(a,b) <- m1; return a }
> 
>Why must g be in MonadZero?  Because the pattern (a,b) is refutable (by
>bottom).
> 

Again, this is the situation under a proposal where MonadZero is still inferred 
for some bindings, as in 1.4, but not for "unfailable" ones as 1.4 would have 
specified - for "refutable" ones.  All of those would count as unfailable under 
1.4 and so none would require MonadZero.

-- James
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Scott Turner

On 2012-01-19 23:52, Michael Snoyman wrote:

maybe I should file a feature request: provide an extra warning
flag (turned on by -Wall) that will warn when you match on a failable
pattern.


I fully agree if it's IO, so that a failed pattern match leads to an 
exception.  The "nice" implementations of fail in the List and Maybe 
monads are a different story.


Ideally one would want to be able to turn on a warning whenever IO is 
used in a way which could generate a pattern match exception.  This 
would call for a type distinction, as you said, "reinstate the MonadZero 
constraint".


Here's an idea that might address SPJ's "killer".
  b) if you add an extra constructor to a single-constructor
 type then pattern matches on the original constructor
 suddenly become failable

Another binding operator might be introduced so that the code would show 
the intention either to have a failable or non-failable pattern match.

 do (x,y) <- pair   failable, requires MonadZero
 do (x,y) <=- pair  requires non-failable pattern
supports Monads that should not fail

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Jacques Carette

On 19/01/2012 10:19 PM, Edward Z. Yang wrote:

  In other words,
MonadZero has no place in dealing with pattern match failure!

I completely agree.  See "Bimonadic semantics for basic pattern matching 
calculi" [1] for an exploration of just that.  In the language of that 
paper, the issue is that there is a monad of effects for actions, and a 
monad of effects for pattern matching, and while these are very lightly 
related, they really are quite different.  By varying both monads, one 
can easily vary through a lot of different behaviour for 
pattern-matching as found in the literature.


I should add that if we had known about some of the deeper structures of 
pattern matching (as in Krishnaswami's Focusing on Pattern Matching [2], 
published 3 years *later*), we could have simplified our work.


Jacques

[1] 
http://www.cas.mcmaster.ca/~kahl/Publications/Conf/Kahl-Carette-Ji-2006a.html

[2] http://www.cs.cmu.edu/~neelk/pattern-popl09.pdf

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-20 Thread Ryan Ingram
I don't currently have anything to add to this discussion, but I want to
encourage you all to keep having it because I think it has potential to
improve the language in the "do things right or don't do them at all"
philosophy that Haskell tends towards.

  -- ryan

On Fri, Jan 20, 2012 at 6:32 AM, Jacques Carette wrote:

> On 19/01/2012 10:19 PM, Edward Z. Yang wrote:
>
>>  In other words,
>> MonadZero has no place in dealing with pattern match failure!
>>
>>  I completely agree.  See "Bimonadic semantics for basic pattern matching
> calculi" [1] for an exploration of just that.  In the language of that
> paper, the issue is that there is a monad of effects for actions, and a
> monad of effects for pattern matching, and while these are very lightly
> related, they really are quite different.  By varying both monads, one can
> easily vary through a lot of different behaviour for pattern-matching as
> found in the literature.
>
> I should add that if we had known about some of the deeper structures of
> pattern matching (as in Krishnaswami's Focusing on Pattern Matching [2],
> published 3 years *later*), we could have simplified our work.
>
> Jacques
>
> [1] http://www.cas.mcmaster.ca/~**kahl/Publications/Conf/Kahl-**
> Carette-Ji-2006a.html
> [2] 
> http://www.cs.cmu.edu/~neelk/**pattern-popl09.pdf
>
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-21 Thread Ganesh Sittampalam
On 20/01/2012 03:23, Edward Z. Yang wrote:
> Oh, I'm sorry! On a closer reading of your message, you're asking not
> only asking why 'fail' was added to Monad, but why unfailable patterns
> were removed.
> 
> Well, from the message linked:
> 
> In Haskell 1.4 g would not be in MonadZero because (a,b) is unfailable
> (it can't fail to match).  But the Haskell 1.4 story is unattractive 
> becuase
> a) we have to introduce the (new) concept of unfailable
> b) if you add an extra constructor to a single-constructor type
>then pattern matches on the original constructor suddenly 
> become
>failable
> 
> (b) is a real killer: suppose that you want to add a new constructor and
> fix all of the places where you assumed there was only one constructor.
> The compiler needs to emit warnings in this case, and not silently transform
> these into failable patterns handled by MonadZero...

It's pretty ugly, but what about using a different 'do' to select the
MonadZero behaviour? "failable-do Foo x <- bar" translates to mzero,
whereas "do Foo x <- bar" translates to an error. That way programmer
intent is captured locally.

"failable-do" is a straw man name :-)

Ganesh

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-24 Thread Michael Snoyman
On Fri, Jan 20, 2012 at 6:52 AM, Michael Snoyman  wrote:
> On Fri, Jan 20, 2012 at 6:41 AM, Edward Z. Yang  wrote:
>> Aw, that is really suboptimal.  Have you filed a bug?
>
> I think it's a feature, not a bug. When dealing with monads that
> provide nice[1] implementations of `fail`, you can (ab)use this to
> avoid writing a bunch of case expressions. I remember reading it in
> one of the first tutorials on Haskell I looked at (four years ago now?
> you can see how much this bothered me if I still remember that).
>
> I admit that there are some use cases where the current behavior is
> convenient, but I think we're paying too steep a price. If we got rid
> of this feature entirely, we could (a) get rid of fail and (b) have
> the compiler warn us about a bunch of errors at compile time.
>
> But maybe I should file a feature request: provide an extra warning
> flag (turned on by -Wall) that will warn when you match on a failable
> pattern. Essentially, I would want:
>
> SomeConstr args <- someAction
>
> to be interpreted as:
>
> temp <- someAction
> case temp of
>    SomeConstr args ->
>
> Michael

I've filed a feature request for this warning:

http://hackage.haskell.org/trac/ghc/ticket/5813

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why were unfailable patterns removed and "fail" added to Monad?

2012-01-26 Thread Scott Turner

On 2012-01-24 05:32, Michael Snoyman wrote:

On Fri, Jan 20, 2012 at 6:52 AM, Michael Snoyman  wrote:

provide an extra warning flag (turned on by -Wall) that will

>> warn when you match on a failable pattern.


I've filed a feature request for this warning:
http://hackage.haskell.org/trac/ghc/ticket/5813


Thanks!  I wish the compiler could tell the difference between monads 
that handle failure nicely (e.g. List) and those that throw a runtime 
error (e.g. IO).


Something's wrong -- I'm feeling nostalgic for MonadZero.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe