
I would like to suggest a correction to ticket #56, "Pattern Guards". It is easy to show that every expression written using pattern guards can also be written in Haskell 98 in a way that is essentially equivalent in simplicity. (Proof below.) In my opinion, the Haskell 98 version below is more clear than the pattern guard version - it makes the monad explicit. Even if you disagree, I think it would be very difficult to argue that the difference is important enough to justify the extreme measure of adding new syntax to the language. Therefore, the first two items under "Pros" are false, and should be removed. The only remaining "Pro" is that the extension is well-specified, which has no value on its own. The purpose of Haskell' is to remove warts from Haskell, not add new ones. Pattern guards are a serious wart - they further overload syntax that is arguably already overused, as pointed out in the referenced paper by Martin Erwig and Simon Peyton Jones [EPJ]. I hope that there is still time to retract the evil decree of "definitely in" Proposal Status for this ticket. Regards, Yitz Proof: We first assume that the following declarations are available, presumably from a library:
data Exit e a = Continue a | Exit {runExit :: e} instance Monad (Exit e) where return = Continue Continue x >>= f = f x Exit e >>= _ = Exit e
(Note that this is essentially the same as the Monad instance for Either defined in Control.Monad.Error, except without the restriction that e be an instance of Error.)
maybeExit :: Maybe e -> Exit e () maybeExit = maybe (return ()) Exit
Now given any function binding using pattern guards: funlhs | qual11, qual12, ..., qual1n = exp1 | qual21, qual22, ..., qual2n = exp2 ... we translate the function binding into Haskell 98 as: funlhs = runExit $ do maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)} ... where qualij' -> pat <- return (e) if qualij is pat <- e qualij' -> guard (qualij) if qualij is a boolean expression qualij' -> qualij if qualij is a let expression For a conventional guard: | p = exp we can simplify the translation to: when (p) $ Exit (exp) Simplifications are also possible for other special cases. This concludes the proof. Here are some examples, taken from [EPJ]:
clunky env var1 var2 | Just val1 <- lookup env var1 , Just val2 <- lookup env var2 = val1 + val2 ...other equations for clunky
translates to:
clunky env var1 var2 = runExit $ do maybeExit $ do val1 <- lookup env var1 val2 <- lookup env var2 return (val1 + val2) ...other equations for clunky
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs | Just (y,ys) <- lview xs, p y = lcons y (filtSeq p ys) | Just (y,ys) <- lview xs = filtSeq p ys | otherwise = nil
translates to:
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs = runExit $ do maybeExit $ do (y,ys) <- lview xs guard $ p y return $ lcons y $ filtSeq p ys maybeExit $ do (y,ys) <- lview xs return $ filtSeq p ys Exit nil
Note that in this case, the Maybe monad alone is sufficient. That eliminates both the double lookup and the double pattern match, as discussed in [EPJ]:
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs = fromMaybe nil $ do (y,ys) <- lview xs return $ if (p y) then lcons y (filtSeq p ys) else filtSeq p ys

On Thu, Sep 28, 2006 at 04:40:30PM +0300, Yitzchak Gale wrote:
Now given any function binding using pattern guards:
funlhs | qual11, qual12, ..., qual1n = exp1 | qual21, qual22, ..., qual2n = exp2 ...
we translate the function binding into Haskell 98 as:
funlhs = runExit $ do maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)} ...
Or even funlhs = fromJust $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} `mplus` do {qual21'; qual22'; ...; qual2n'; return (exp2)}

Hi Yitzchak Gale wrote:
I would like to suggest a correction to ticket #56, "Pattern Guards".
It is easy to show that every expression written using pattern guards can also be written in Haskell 98 in a way that is essentially equivalent in simplicity. (Proof below.)
Whether or not your conclusion is correct, your candidate proof is incomplete.
funlhs | qual11, qual12, ..., qual1n = exp1 | qual21, qual22, ..., qual2n = exp2 ...
we translate the function binding into Haskell 98 as:
funlhs = runExit $ do maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)} ...
This translation does not appear to address programs with multiple left-hand sides, exploiting fall-through from match (hence guard) failure, eg varVal :: String -> [(String, String)] -> String varVal x locals | Just y <- lookup x locals = y varVal "X" xys = "42" varVal _ _ = error "var not found" Haskell 98 provides no means to inspect the value of an intermediate computation (something other than an argument or component thereof) without committing to one right-hand side. I think that's rather unfortunate, because it loses the visual tabulation of the possibilities and priorities. I'm not a big fan of pattern guards, though, because they only give you one shot at matching the intermediate result. Some means to do 'case e' on the left would be nice. Maybe gcd x y | compare x y -> LT = gcd x (y - x) GT = gcd (x - y) y gcd x _ = x or some such. I wish I could think of a better example without too much context, but such a thing escapes me for the moment. In general, I think it's good to collocate on the left as much as possible of a function's scrutineering. Stringing out ifs and cases makes it harder to see what's going on. All the best Conor

Hello Conor, Thursday, September 28, 2006, 10:30:46 PM, you wrote:
gcd x y | compare x y -> LT = gcd x (y - x) GT = gcd (x - y) y gcd x _ = x
or some such. I wish I could think of a better example without too much context, but such a thing escapes me for the moment. In general, I think it's good to collocate on the left as much as possible of a function's scrutineering. Stringing out ifs and cases makes it harder to see what's going on.
i like this. for me, left part of function definition is a half of logical programming language, it only omits two-direction pattern-matching mechanism -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello,
This particular example we can do with pattern guards
(although it seems that a simple 'case' is more appropriate for this example)
On 9/28/06, Bulat Ziganshin
Hello Conor,
Thursday, September 28, 2006, 10:30:46 PM, you wrote:
gcd x y | compare x y -> LT = gcd x (y - x) GT = gcd (x - y) y gcd x _ = x
mygcd x y | LT <- z = mygcd x (y-x) | GT <- z = mygcd (x-y) y where z = compare x y mygcd x _ = x -Iavor

Hello,
I think that pattern guards are a nice generalization of ordinary
guards and they should be added to the language. Of course, as you
point out, we can encode them using the Maybe monad, but the same is
true for nested patterns, and I don't think that they should be
removed from Haskell. I think that the benefit of adding pattern
guards is similar to that of using nested patterns: it provides a
concise notation that is easy to explain and understand without having
to first learn about monads (even though there is a monad that is
hidden behind the scenes). This, combined with the fact that pattern
guards are quite easy to implement, I think advocates in their favor.
-Iavor
On 9/28/06, Yitzchak Gale
I would like to suggest a correction to ticket #56, "Pattern Guards".
It is easy to show that every expression written using pattern guards can also be written in Haskell 98 in a way that is essentially equivalent in simplicity. (Proof below.)
In my opinion, the Haskell 98 version below is more clear than the pattern guard version - it makes the monad explicit. Even if you disagree, I think it would be very difficult to argue that the difference is important enough to justify the extreme measure of adding new syntax to the language.
Therefore, the first two items under "Pros" are false, and should be removed. The only remaining "Pro" is that the extension is well-specified, which has no value on its own.
The purpose of Haskell' is to remove warts from Haskell, not add new ones. Pattern guards are a serious wart - they further overload syntax that is arguably already overused, as pointed out in the referenced paper by Martin Erwig and Simon Peyton Jones [EPJ].
I hope that there is still time to retract the evil decree of "definitely in" Proposal Status for this ticket.
Regards, Yitz
Proof: We first assume that the following declarations are available, presumably from a library:
data Exit e a = Continue a | Exit {runExit :: e} instance Monad (Exit e) where return = Continue Continue x >>= f = f x Exit e >>= _ = Exit e
(Note that this is essentially the same as the Monad instance for Either defined in Control.Monad.Error, except without the restriction that e be an instance of Error.)
maybeExit :: Maybe e -> Exit e () maybeExit = maybe (return ()) Exit
Now given any function binding using pattern guards:
funlhs | qual11, qual12, ..., qual1n = exp1 | qual21, qual22, ..., qual2n = exp2 ...
we translate the function binding into Haskell 98 as:
funlhs = runExit $ do maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)} ...
where
qualij' -> pat <- return (e) if qualij is pat <- e qualij' -> guard (qualij) if qualij is a boolean expression qualij' -> qualij if qualij is a let expression
For a conventional guard:
| p = exp
we can simplify the translation to:
when (p) $ Exit (exp)
Simplifications are also possible for other special cases.
This concludes the proof. Here are some examples, taken from [EPJ]:
clunky env var1 var2 | Just val1 <- lookup env var1 , Just val2 <- lookup env var2 = val1 + val2 ...other equations for clunky
translates to:
clunky env var1 var2 = runExit $ do maybeExit $ do val1 <- lookup env var1 val2 <- lookup env var2 return (val1 + val2) ...other equations for clunky
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs | Just (y,ys) <- lview xs, p y = lcons y (filtSeq p ys) | Just (y,ys) <- lview xs = filtSeq p ys | otherwise = nil
translates to:
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs = runExit $ do maybeExit $ do (y,ys) <- lview xs guard $ p y return $ lcons y $ filtSeq p ys maybeExit $ do (y,ys) <- lview xs return $ filtSeq p ys Exit nil
Note that in this case, the Maybe monad alone is sufficient. That eliminates both the double lookup and the double pattern match, as discussed in [EPJ]:
filtSeq :: (a->Bool) -> Seq a -> Seq a filtSeq p xs = fromMaybe nil $ do (y,ys) <- lview xs return $ if (p y) then lcons y (filtSeq p ys) else filtSeq p ys
Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Iavor Diatchki wrote:
...we can encode them using the Maybe monad, but the same is true for nested patterns, and I don't think that they should be removed from Haskell.
The fact that pattern guards can be "encoded as monads" is not the problem. The problem is that they are a confusing syntax that does not add anything new.
I think that the benefit of adding pattern guards is... it provides a concise notation
Not significantly more concise than existing notation.
that is easy to explain and understand
As an educator, I disagree. What does "pat <- exp" mean? It has a completely new meaning here, just similar enough to existing semantics to be very confusing.
without having to first learn about monads
Why is everyone so afraid of monads? They are one of the most beatiful and useful features of Haskell, and one uses them all the time in even the simplest programs. It is not hard to give a beginner a basic, practical, working knowledge of the common monads. Deeper understanding can come later. I think this should be added right near the beginning of every Haskell tutorial.
...pattern guards are quite easy to implement...
Yes, pattern guards are low-hanging fruit for compiler implementors. They seem so obvious and easy to understand for those of us who have been in the habit of using them. But I think it is time to step back and take a more objective look at them. -Yitz

On Fri, Sep 29, 2006 at 02:59:49AM +0300, Yitzchak Gale wrote:
Iavor Diatchki wrote:
I think that the benefit of adding pattern guards is... it provides a concise notation
Not significantly more concise than existing notation.
That's just not true. If all your pattern guards happen to involve the Maybe monad, then perhaps you can rewrite the pattern guard code almost as concisely using monadic notation, but it does mean that the moment you choose to do that you have to completely give up on using Haskell's existing pattern matching to define your function, unless you happen to be defining a particularly simple function. How do you nearly as concisely write a function such as this in Haskell 98?
foo (Left "bar") = "a" foo (Right x) | (b,"foo") <- break (==' ') x = "b " ++ b foo (Left x) | ("foo",c) <- break (==' ') x = "c " ++ c foo (Right x) | ["Hello",n,"how","are","you",d@(_:_)] <- words x, last d == '?' = n ++ " is not here right now, but " ++ n ++ " is " ++ init d ++ " fine." foo (Left x) | length x == 13 = "Unlucky!" foo (Right x) = x foo (Left x) = x
It's a contrived example, but the usefulness of pattern guards is only greater on more realistic, more complicated functions. -- David Roundy

I'm not argueing against pattern guards (nor for them;-), but perhaps the attached translations of Conor's and David's examples might help to dispel some myths. For the translation idea, see my earlier email: http://www.haskell.org/pipermail/haskell-prime/2006-February/000597.html If it wasn't for those pesky returns/guards, one might claim the translations to be as concise as the originals. As it stands, the results of the translation are rather more awkward but -and this is the important point- pattern guards do not add new functionality. And fortunately, David only asked for "nearly as concise":) hth, Claus

Claus Reinke wrote:
If it wasn't for those pesky returns/guards, one might claim the translations to be as concise as the originals. As it stands, the results of the translation are rather more awkward but -and this is the important point- pattern guards do not add new functionality.
Well, neither do Boolean guards nor even basic pattern matching (with respect to case expressions). I'm not necessarily in favour of pattern guards exactly as formulated, but I am in favour of thinking about syntax to support a more readable presentation of the scrutiny process by which functions make choices. Things to minimise include (1) Wiring: naming a thing in order to inspect it, as in mygcd x y | LT <- z = mygcd x (y-x) | GT <- z = mygcd (x-y) y where z = compare x y mygcd x _ = x The version I proposed gcd x y | compare x y -> LT = gcd x (y - x) GT = gcd (x - y) y gcd x _ = x avoided the need for this indirection via z and the dislocation of (compare x y) from the patterns which give it relevance. I want to present a direct tabulation of patterns visibly headed by the expression they analyse. It's far more comprehensible. (2) Monadic noise: one simply should not need to clutter a program with do, return, mplus and fromJust (ugh!), spelling out the semantics of pattern matching in minute detail. For at least 36 years, we've been able to hide all that junk behind a highly readable equational notation. This is one monad we don't need to see. (3) Early commitment to one particular right-hand side: without pattern guards, we're forced to the right if we want to examine the result of an intermediate computation. This means we have to do any subsequent analysis using the syntax of expressions which is much clunkier than that of left-hand sides. Pattern guards as proposed give us a bare minimum, a one-shot match: more patterns require wiring. The notation I suggested is a modest improvement, allowing multiple attempts to match, but it's still not as general as it might be. If, for example, we wanted to analyse one of the original pattern variables further, in the light of a case on an intermediate value, we're stuffed. In general, I'd like to be able to compact programs written with helper functions, eg gcd x y = help x y (compare x y) where help 0 y LT = y help x y LT = gcd x (y - x) help x 0 GT = x help x y GT = gcd (x - y) y help x _ _ = x Introducing the helper just adds an 'extra column' for (compare x y), and then we can do what we like! I'd quite like to inline this a little. Apologies for the wildly made-up notation gcd x y | compare x y -> -- just introduces new column gcd 0 y , LT = y gcd x y , LT = gcd x (y - x) gcd x 0 , GT = x gcd x y , GT = gcd (x - y) y gcd x _ , _ = x I'd adopt the convention that omitting the lhs, just means the gets copied from left of the |, so we recover my earlier notation as a special case, and we don't get punished for /not/ inspecting pattern variables further. Yes, I know the example is contrived, but as David points out, it's hard to come up with simple examples of phenomena which tend to bite in more complex situations. I'm guessing this is all too wild and woolly for haskell-prime, but I thought I'd try to survey a bit more of the design space in the interests of an effective compromise. All of these programs can be turned into decision trees made from let and case-on-variable: the question is to what extent we support the compression of these trees as contingency tables for the sake of clarity. Do we give up at the first let? At the first non-Boolean let? At the first let x not immediately followed by some favoured pattern of case x? When? The recodings of the pattern guard programs we've seen so far strike me as eloquent arguments in favour of adopting at least the notion of pattern guards from the original proposal. All the best Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Thanks for all the responses. I get the digest, and I was off-line for a day, so I only saw most of them now. Also, for the same reason, my apologies that I am connecting this message to the wrong spot in the thread. First of all, I still maintain that any expression written using pattern guards can be written just as simply - and, in my opinion, more clearly - in Haskell 98 using monads. An important clarification: the main monad at work here is the Exit monad. The "bind" notation in a pattern guard is just an obfuscated Exit monad. However, in many simple examples, the Maybe monad can be used as a special case of the Exit monad. It is true that in my proof I also use a nested Maybe monad, but that is only for the comma-separated sequence of multiple qualifiers in a complex pattern guard. Conor McBride wrote:
Whether or not your conclusion is correct, your candidate proof is incomplete... This translation does not appear to address programs with multiple left-hand sides, exploiting fall-through from match (hence guard) failure
Quite right, sorry. That is easy to fix. A corrected proof is at the bottom of this message. David Roundy wrote:
If all your pattern guards happen to involve the Maybe monad, then perhaps you can rewrite the pattern guard code almost as concisely using monadic notation
No, it works for any type.
the moment you choose to do that you have to completely give up on using Haskell's existing pattern matching to define your function, unless you happen to be defining a particularly simple function.
No, all pattern matching is retained as before.
How do you nearly as concisely write a function such as this in Haskell 98?
Hmm, believe it or not, your original example is too simple. You can actually do the whole thing in the Maybe monad, because none of the versions of foo has more than one pattern guard. I am transposing the third and fourth foo and combinig like LHSs to make it more interesting. Here is your function with those modifications:
foo (Left "bar") = "a" foo (Right x) | (b,"foo") <- break (==' ') x = "b " ++ b | ["Hello",n,"how","are","you",d@(_:_)] <- words x, last d == '?' = n ++ " is not here right now, but " ++ n ++ " is " ++ init d ++ " fine." foo (Left x) | ("foo",c) <- break (==' ') x = "c " ++ c | length x == 13 = "Unlucky!" foo (Right x) = x foo (Left x) = x
And here it is in Haskell 98:
foo (Left "bar") = "a" foo (Right x) | isExit y = runExit y where y = do maybeExit $ do (b,"foo") <- return $ break (==' ') x return $ "b" ++ b maybeExit $ do ["Hello",n,"how","are","you",d@(_:_)] <- return $ words x guard $ last d == '?' return $ n ++ " is not here right now, but " ++ n ++ " is " ++ init d ++ " fine." foo (Left x) | isExit y = runExit y where y = do maybeExit $ do ("foo",c) <- break (==' ') x return $ "c" ++ c when (length x == 13) $ Exit "Unlucky!" foo (Right x) = x foo (Left x) = x
Finally, here is the corrected proof, allowing for multiple LHSs. Actually, the proof is still not complete - I do not treat pattern bindings, nor other possible forms for funlhs, as enumerated in the Report. Proof: We first assume that the following declarations are available, presumably from a library:
data Exit e a = Continue a | Exit {runExit :: e} instance Monad (Exit e) where return = Continue Continue x >>= f = f x Exit e >>= _ = Exit e
(Note that this is essentially the same as the Monad instance for Either defined in Control.Monad.Error, except without the restriction that e be an instance of Error.)
maybeExit :: Maybe e -> Exit e () maybeExit = maybe (return ()) Exit
isExit :: Exit e a -> Bool isExit (Exit _) = True isExit _ = False
Now given any function binding using pattern guards: var apat1 apat2 ... apatn | qual11, qual12, ..., qua11n = exp1 | qual21, qual22, ..., qual2n = exp2 ... we translate the function binding into Haskell 98 as: var apat1 apat2 ... apatn | isExit y = runExit y where {y = do maybeExit $ do {qual11'; qual12'; ...; qual1n'; return (exp1)} maybeExit $ do {qual21'; qual22'; ...; qual2n'; return (exp2)} ...} where y is a new variable qualij' -> pat <- return (e) if qualij is pat <- e qualij' -> guard (qualij) if qualij is a boolean expression qualij' -> qualij if qualij is a let expression -Yitz

Conor McBride wrote:
Claus Reinke wrote:
...the results of the translation are rather more awkward but -and this is the important point- pattern guards do not add new functionality.
Well, neither do Boolean guards nor even basic pattern matching... one simply should not need to clutter a program with do, return, mplus and fromJust (ugh!), spelling out the semantics of pattern matching in minute detail. For at least 36 years, we've been able to hide all that junk behind a highly readable equational notation. This is one monad we don't need to see.
Some complex things are happening: selections and bindings are happening at the same time. The monad spells it out clearly and concisely, without adding very much weight at all. Function definitions appear visually almost the same, with or without the pattern guards. There has to be a really, really compelling reason to add new syntax to a language. Every bit of new syntax makes a language harder to learn, and less usable for the general user.
without pattern guards, we're forced to the right if we want to examine the result of an intermediate computation. This means we have to do any subsequent analysis using the syntax of expressions which is much clunkier than that of left-hand sides.
Nice point. -Yitz

On 10/1/06, Yitzchak Gale
Conor McBride wrote:
Claus Reinke wrote:
...the results of the translation are rather more awkward but -and this is the important point- pattern guards do not add new functionality.
Well, neither do Boolean guards nor even basic pattern matching... one simply should not need to clutter a program with do, return, mplus and fromJust (ugh!), spelling out the semantics of pattern matching in minute detail. For at least 36 years, we've been able to hide all that junk behind a highly readable equational notation. This is one monad we don't need to see.
Some complex things are happening: selections and bindings are happening at the same time. The monad spells it out clearly and concisely, without adding very much weight at all.
I would argue that most Haskell programmers would *never* write the various snippets of code demonstrated in this thread in your way, on the other hand pattern guards are convenient and easy enough to understand (i.e. you don't have to know very much about monads), and probably would get used. I certainly use them (and I *do* understand monads enough to switch to your style of coding if I wanted to)! Your way is nice and elegant if you happen to know enough to understand it, pattern guards are nice and elegant to people who don't.
There has to be a really, really compelling reason to add new syntax to a language. Every bit of new syntax makes a language harder to learn, and less usable for the general user.
I disagree. Adding syntactic sugar is cheap, as long as the core concepts are small and elegant. I believe Haskell has taken this approach so far (or do you want to get rid of e.g. list comprehensions as well? They too are expressible quite elegantly with monads.), and I think pattern guards are an excellent candidate in line with this. It's a "natural" (in terms of "feel", fuzzy I know) generalisation of guards, and simply won't affect anyone who think they are difficult in any way. They are and intuitive and nice. They don't change the behaviour of the "core" language, all they do is add a tiny bit of syntactic sugar to make programmer's lives a little bit easier - and they're not even adding anything completely new, just extending existing features. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Sebastian Sylvan wrote:
I would argue that most Haskell programmers would *never* write the various snippets of code demonstrated in this thread in your way,
I agree, too. I am not advocating that people should write code exactly that way in real life. My construction is meant to be a proof that pattern guards do not provide any significant simplification even in the worst case. In real life, the monadic approach usually leads to a significant simplification. I find that whenever I feel an urge to use a pattern guard, it is a sure sign that I have landed in the wrong monad. I step back and look again at my overall design, and the result is invariably much better code. And the urge goes away.
Adding syntactic sugar is cheap, as long as the core concepts are small and elegant.
The graveyard is littered with the remains of programming languages that took that approach and met an ignoble end. The entire language must remain small and elegant - not just the individual pieces of new syntax that are bolted on. Feature-creep is what eventually kills every programming language. Since Haskell is already a mature language as it first becomes adapted for general use, we need to be especially vigilant. -Yitz

On Sun, Oct 01, 2006 at 02:08:35AM +0200, Yitzchak Gale wrote:
David Roundy wrote:
foo (Left "bar") = "a" foo (Right x) | (b,"foo") <- break (==' ') x = "b " ++ b | ["Hello",n,"how","are","you",d@(_:_)] <- words x, last d == '?' = n ++ " is not here right now, but " ++ n ++ " is " ++ init d ++ " fine." foo (Left x) | ("foo",c) <- break (==' ') x = "c " ++ c | length x == 13 = "Unlucky!" foo (Right x) = x foo (Left x) = x
And here it is in Haskell 98:
foo (Left "bar") = "a" foo (Right x) | isExit y = runExit y where y = do maybeExit $ do (b,"foo") <- return $ break (==' ') x return $ "b" ++ b maybeExit $ do ["Hello",n,"how","are","you",d@(_:_)] <- return $ words x guard $ last d == '?' return $ n ++ " is not here right now, but " ++ n ++ " is " ++ init d ++ " fine." foo (Left x) | isExit y = runExit y where y = do maybeExit $ do ("foo",c) <- break (==' ') x return $ "c" ++ c when (length x == 13) $ Exit "Unlucky!" foo (Right x) = x foo (Left x) = x
I disagree as far as the beauty of this approach. You require that every pattern guard involves a where binding, plus the use of a three function calls (isExit, runExit and maybeExit, plus sometimes one or more calls to guard). In my opinion that makes it less concise than the usual pattern matching approach. One extra where binding may not much matter in simple functions like this, but in complicated functions that are already hard to read and understand (because they do complicated things, not because they're poorly written), throwing in extra where bindings is just a waste. Also, in your code you're forced to mingle the "pattern matching" with the actual code itself, which to me makes the result less legible. And would be even worse if the function were one that returns a monadic result, so the reader would be forced to distinguish between the do in the Exit monad and the do in the output monad. Pattern guards feel very natural, are very easy to read, and won't bother you if you don't use them. As you point, they're just syntactic sugar, and therefore are "safe", in that they can't lead to any weird or confusing semantics. -- David Roundy

Just a few thoughts, It is well known pattern guards can be simulated with haskell 98, I don't think anyone has doubted that. The need for supplemental condition testing and splitting the pattern matching among the where clause and the boolean guards is considered very cumbersome by some. Personally I feel it very much obscures the intent of the programmer and comingles the body of the branch with the matching criteria for it in an unpleasant way. the (<-) notation isn't overloaded at all really, any more than it is in list comprehensions. <- always means monadic bind. it is fully general in 'do'. restricted to the list monad in list comprehensions, and restricted to something like the exit monad you mention in pattern guards. They are all consistent uses of (<-). pattern guards have almost unanimous support for inclusion in haskell'. so, even if a couple people on the comitee switched positions, pattern guards would still most likely end up in. Since they are just syntatic sugar, there cannot be an overriding technical reason they won't work, and it is unlikely that many peoples aethetics of coding will change. John -- John Meacham - ⑆repetae.net⑆john⑈

The need for supplemental condition testing and splitting the pattern matching among the where clause and the boolean guards is considered very cumbersome by some.
Yes, it is. But that was only an artificial construction, meant to work in general. I wouldn't do it that way really. When an individual problem is reformulated in the correct monad, the entire program becomes much simpler.
the (<-) notation isn't overloaded at all really, any more than it is in list comprehensions. <- always means monadic bind. it is fully general in 'do'. restricted to the list monad in list comprehensions, and restricted to something like the exit monad you mention in pattern guards. They are all consistent uses of (<-).
No, they are not the same. Bind in a list comprehension translates to the exact same bind in do notation. I cannot think of any translation of pattern guards for which the same thing is true. For example, in my construction, pat <- e translates to pat <- return (e). That is a very significant semantic difference. -Yitz

On Sun, Oct 01, 2006 at 02:08:35AM +0200, Yitzchak Gale wrote:
An important clarification: the main monad at work here is the Exit monad. The "bind" notation in a pattern guard is just an obfuscated Exit monad. However, in many simple examples, the Maybe monad can be used as a special case of the Exit monad.
You don't use >>=, just >>. Similarly Exit is used only in the form Exit e (), which is equivalent to Maybe e, i.e. if we define exitMaybe :: Exit e () -> Maybe e exitMaybe (Continue _) = Nothing exitMaybe (Exit e) = Just e then we have runExit m = fromJust (exitMaybe m) exitMaybe (x >> y) = exitMaybe x `mplus` exitMaybe y exitMaybe (maybeExit m) = m so we can replace the Exit monad with Maybe.

I wrote:
...the main monad at work here is the Exit monad.
Ross Paterson wrote:
...if we define exitMaybe :: Exit e () -> Maybe e exitMaybe (Continue _) = Nothing exitMaybe (Exit e) = Just e then we have runExit m = fromJust (exitMaybe m) exitMaybe (x >> y) = exitMaybe x `mplus` exitMaybe y exitMaybe (maybeExit m) = m so we can replace the Exit monad with Maybe.
Maybe monads quit on failure and continue on success. We want the opposite semantics for guards, pattern matching, and the like. The Exit monad is the dual of the Maybe monad in this sense. In particular, your identity
exitMaybe (x >> y) = exitMaybe x `mplus` exitMaybe y
is not true. If we let x = Continue () and y = Exit z, then exitMaybe (x >> y) = Just z but exitMaybe x `mplus` exitMaybe y = Nothing -Yitz

On Mon, Oct 02, 2006 at 11:58:44PM +0200, Yitzchak Gale wrote:
Ross Paterson wrote:
...if we define exitMaybe :: Exit e () -> Maybe e exitMaybe (Continue _) = Nothing exitMaybe (Exit e) = Just e
Maybe monads quit on failure and continue on success. We want the opposite semantics for guards, pattern matching, and the like.
And that's what mplus does.
In particular, your identity
exitMaybe (x >> y) = exitMaybe x `mplus` exitMaybe y
is not true. If we let x = Continue () and y = Exit z, then
exitMaybe (x >> y) = Just z
but
exitMaybe x `mplus` exitMaybe y = Nothing
exitMaybe (Continue ()) `mplus` exitMaybe (Exit z) = Nothing `mplus` Just z = Just z

Ross Paterson wrote:
Yitzchak Gale wrote:
Maybe monads quit on failure and continue on success. We want the opposite semantics for guards, pattern matching, and the like.
And that's what mplus does.
In particular, your identity... is not true...
Oops, yes it is, sorry. You are using mplus as the "dual" of (<<) rather than dualiing the monad. -Yitz

On 9/28/06, I wrote:
I would like to suggest a correction to ticket #56, "Pattern Guards".
Here is a summary of the discussion: There seems to be a consensus that the main "Pro" currently listed in the ticket is not the real reason. Pros: - Many people have been accustomed to using this syntax for a long time. - Some people find pattern guards to be elegant and aesthetically pleasing. - The alternative monadic style requires knowledge of monads. - More selections are pushed to the lefthand-side of bindings. - Already implemented in most compilers, appears to be easy to implement. Cons: - The semantics of "<-" are further overloaded in a potentially confusing way. - At least one person does not find pattern guards to be elegant and aesthetically pleasing at all. :) - Some people feel that the net gain, if any, is not worth the cost of changing the syntax of the core of Haskell. (Others do not see it as so much of a change, since it has been available in practice for a long time.) Anything else? -Yitz
participants (10)
-
Bulat Ziganshin
-
Claus Reinke
-
Conor McBride
-
Conor McBride
-
David Roundy
-
Iavor Diatchki
-
John Meacham
-
Ross Paterson
-
Sebastian Sylvan
-
Yitzchak Gale