
Hello, recently I read about pattern guards which are a candidate for Haskell'. As I understand them, their purpose is to provide an easier way to write functions like (taken from the wiki, it does not run): clunky env var1 var1 = case lookup env var1 of Nothing -> fail Just val1 -> case lookup env var2 of Nothing -> fail Just val2 -> val1 + val2 where fail = var1 + var2 Wouldn't
clunky :: Num a => [(a, a)] -> a -> a -> a clunky env var1 var2 = case (lookup var1 env, lookup var2 env) of (Just v1, Just v2) -> v1 + v2 _ -> var1 + var2
be simple enough to make a syntax change superflous? It is so simple, that there is no need for `fail` in Haskell or Haskell' :) schneegloeckchen

schneegloeckchen:
Hello,
recently I read about pattern guards which are a candidate for Haskell'.
As I understand them, their purpose is to provide an easier way to write functions like (taken from the wiki, it does not run):
clunky env var1 var1 = case lookup env var1 of Nothing -> fail Just val1 -> case lookup env var2 of Nothing -> fail Just val2 -> val1 + val2 where fail = var1 + var2
Wouldn't
clunky :: Num a => [(a, a)] -> a -> a -> a clunky env var1 var2 = case (lookup var1 env, lookup var2 env) of (Just v1, Just v2) -> v1 + v2 _ -> var1 + var2
be simple enough to make a syntax change superflous? It is so simple, that there is no need for `fail` in Haskell or Haskell' :)
There's been a previous discussion on this[1]. The joy of pattern guards reveals once you have more conditions. Consider this real world example: clean_ s| Just _ <- no_io `matchRegex` s = "No IO allowed\n" | Just _ <- terminated `matchRegex` s = "Terminated\n" | Just _ <- hput `matchRegex` s = "Terminated\n" | Just _ <- outofmem `matchRegex` s = "Terminated\n" | Just _ <- stack_o_f `matchRegex` s = "Stack overflow\n" | Just _ <- loop `matchRegex` s = "Loop\n" | Just _ <- undef `matchRegex` s = "Undefined\n" | Just _ <- type_sig `matchRegex` s = "Add a type signature\n" | Just (_,m,_,_) <- ambiguous `matchRegexAll` s = m | Just (_,_,b,_) <- inaninst `matchRegexAll` s = clean_ b | Just (_,_,b,_) <- irc `matchRegexAll` s = clean_ b | Just (_,m,_,_) <- nomatch `matchRegexAll` s = m | Just (_,m,_,_) <- notinscope `matchRegexAll` s = m | Just (_,m,_,_) <- hsplugins `matchRegexAll` s = m | Just (a,_,_,_) <- columnnum `matchRegexAll` s = a | Just (a,_,_,_) <- extraargs `matchRegexAll` s = a | Just (_,_,b,_) <- filename' `matchRegexAll` s = clean_ b | Just (a,_,b,_) <- filename `matchRegexAll` s = a ++ clean_ b | Just (a,_,b,_) <- filepath `matchRegexAll` s = a ++ clean_ b | Just (a,_,b,_) <- runplugs `matchRegexAll` s = a ++ clean_ b | otherwise = s -- Don 1. http://www.haskell.org/pipermail/haskell-prime/2006-September/001689.html

Hi
clunky env var1 var1 = case lookup env var1 of Nothing -> fail Just val1 -> case lookup env var2 of Nothing -> fail Just val2 -> val1 + val2 where fail = var1 + var2
Wouldn't
clunky :: Num a => [(a, a)] -> a -> a -> a clunky env var1 var2 = case (lookup var1 env, lookup var2 env) of (Just v1, Just v2) -> v1 + v2 _ -> var1 + var2
The main advantage of pattern guards (to me at least) is that they can appear on the LHS, so failing to match can result in fall through. Everything else has to come on the RHS, meaning you have pick the RHS by this point. This is bad because it now means two entirely separate alternatives just got merged into one, reducing program readability. I would love this to be in Haskell'. In fact, if we could only pick one thing to go in Haskell', I would pick pattern guards. I would have used pattern guards about 15 times today, if they were in Haskell. Compare that to rank-2 types (never needed), MPTC (needed once ever) etc. and you can see why I want this! Thanks Neil

Donald Bruce Stewart
The joy of pattern guards reveals once you have more conditions.
Of course, this is not really the joy of pattern guards. It is the joy of monads, with perhaps a few character strokes saved by a confusing overloading of (<-). But some people do seem to be used to this notation by now. So perhaps a good compromise would be to use a different operator for pattern guards, e.g. (<<-), instead of (<-). What do you say? Yitz

On Wed, 13 Dec 2006, Yitz Gale wrote:
Donald Bruce Stewart
writes: The joy of pattern guards reveals once you have more conditions.
Of course, this is not really the joy of pattern guards. It is the joy of monads, with perhaps a few character strokes saved by a confusing overloading of (<-).
I don't find it any more confusing than the overloading of ->. Note that it's not (<-) - it's not an operator. -- flippa@flippac.org Sometimes you gotta fight fire with fire. Most of the time you just get burnt worse though.

Donald Bruce Stewart
The joy of pattern guards reveals once you have more conditions.
I wrote:
Of course, this is not really the joy of pattern guards. It is the joy of monads, with perhaps a few character strokes saved by a confusing overloading of (<-).
Philippa Cowderoy wrote:
I don't find it any more confusing than the overloading of ->.
You mean that it is used both for lambda abstractions and for functional dependencies? True, but those are so different that there is no confusion.
Note that it's not (<-) - it's not an operator.
Right, it is syntactic sugar for a monad. But this syntax is already used in two places: do notation and list comprehensions. The semantics are exactly the same in both existing uses. The semantics of the proposed new use in pattern guards is quite different, as was discussed in the previous thread. Yet close enough to be confused. There seems to be a consensus that pattern guards are here to stay. So I am proposing to mitigate the damage somewhat by using a different but similar symbol . That matches the different but similar semantics. I mentioned (<<-) as one possibility. Regards, Yitz

Philippa Cowderoy wrote:
I don't find it any more confusing than the overloading of ->.
I wrote:
You mean that it is used both for lambda abstractions and for functional dependencies? True, but those are so different that there is no confusion.
Oh, and case. Also quite different. But, hmm, perhaps that is also getting to be a bit much. In fact, now I think I recall seeing some mention of that in discussions about fundep syntax. Anyway, existing problems are not an excuse to repeat the mistake and make matters even worse. Regards, Yitz

On Wed, 13 Dec 2006, Yitzchak Gale wrote:
Philippa Cowderoy wrote:
I don't find it any more confusing than the overloading of ->.
I wrote:
You mean that it is used both for lambda abstractions and for functional dependencies? True, but those are so different that there is no confusion.
Oh, and case. Also quite different.
This is what I get for replying straight away!
Anyway, existing problems are not an excuse to repeat the mistake and make matters even worse.
I think my point is that I'm not aware of many people who actually think this is a problem or get confused. -- flippa@flippac.org There is no magic bullet. There are, however, plenty of bullets that magically home in on feet when not used in exactly the right circumstances.

Philippa Cowderoy wrote:
This is what I get for replying straight away!
Oh, no, I'm happy that you responded quickly.
I think my point is that I'm not aware of many people who actually think this is a problem or get confused.
Well, I don't mean that this is something that experienced Haskell programmers will stop and scratch their heads over. But the more of these kinds of inconsistencies you have, the worse it is for a programming language. The effect is cumulative. When there are too many of them, they make the language feel heavy, complex, and inelegant. They increase the number of careless errors. They put off beginners. Regards, Yitz

Hi,
I am not clear why you think the current notation is confusing...
Could you give a concrete example? I am thinking of something along
the lines: based on how "<-" works in list comprehensions and the do
notation, I would expect that pattern guards do XXX but instead, they
confusingly do YYY. I think that this will help us keep the
discussion concrete.
-Iavor
On 12/13/06, Yitzchak Gale
Philippa Cowderoy wrote:
This is what I get for replying straight away!
Oh, no, I'm happy that you responded quickly.
I think my point is that I'm not aware of many people who actually think this is a problem or get confused.
Well, I don't mean that this is something that experienced Haskell programmers will stop and scratch their heads over.
But the more of these kinds of inconsistencies you have, the worse it is for a programming language. The effect is cumulative. When there are too many of them, they make the language feel heavy, complex, and inelegant. They increase the number of careless errors. They put off beginners.
Regards, Yitz _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

I am not clear why you think the current notation is confusing... Could you give a concrete example? I am thinking of something along the lines: based on how "<-" works in list comprehensions and the do notation, I would expect that pattern guards do XXX but instead, they confusingly do YYY. I think that this will help us keep the discussion concrete.
consider the following examples: -- do-notation: explicit return; explicit guard; monadic result d _ = do { Just b <- return (Just True); guard b; return 42 } -- list comprehension: explicit return; implicit guard; monadic (list) result lc _ = [ 42 | Just b <- return (Just True), b ] -- pattern guard: implicit return; implicit guard; non-monadic result pg _ | Just b <- Just True, b = 42 in spite of their similarity, all of these constructs handle some of the monadic aspects differently. the translations of pattern guards not only embed statements in "guard", they also embed the right hand sides of generators in "return". translations of list comprehensions only lift statements. translation of do-notation lifts neither statements nor generators. does this clarify things? Claus

Hi
in spite of their similarity, all of these constructs handle some of the monadic aspects differently. the translations of pattern guards not only embed statements in "guard", they also embed the right hand sides of generators in "return". translations of list comprehensions only lift statements. translation of do-notation lifts neither statements nor generators.
does this clarify things?
No. Pattern guards are "obvious", they could only work in one particular way, and they do work that way. They make common things easier, and increase abstraction. If your only argument against them requires category theory, then I'd say that's a pretty solid reason for them going in. The argument that people seem to be making is that they are confusing, I completely disagree. f value | Just match <- lookup value list = g match Without thinking too hard, I am curious how anyone could get the meaning of this wrong if they understand the rest of Haskell. Can you show a concrete example, where you think a user would get confused? Thanks Neil

does this clarify things?
No. Pattern guards are "obvious", they could only work in one particular way, and they do work that way. They make common things easier, and increase abstraction. If your only argument against them requires category theory, then I'd say that's a pretty solid reason for them going in.
sigh.. slow down please, will you? you addressed this reply to me. yet I have been careful, each time this topic comes up, to argue neither in favour nor against pattern guards. instead, my purpose has been to clarify misconceptions, eg., by demonstrating how pattern guards, even though they do add substantial convenience, do not add fundamentally new expressiveness (they can be replaced by a local rewrite), or in this case by providing the examples Iavor asked for, showing the difference in three uses of '<-' as generators and booleans as guards. I do not mind if pattern guards make it into Haskell, precisely because I know how to sugar them away - once all implementations support them, I might even use them more. Nevertheless, I wanted to support Yitzchak's argument, namely that '<-' is used for generators in monadic contexts, but its use in pattern guards is different from that in list comprehensions and do. pattern guards are useful, once explained, but there is nothing particularly obvious about them, nor is there only one way to formulate them: the usual argument that they are just list comprehension syntax transferred to guards breaks down because of the differences Yitzchak is concerned about, and the correspondent claiming to be apfelmus has already shown that a direct embedding of Maybes would be at least as natural as the current implicit embedding into the effect-free part of an unknown monad.
The argument that people seem to be making is that they are confusing, I completely disagree.
f value | Just match <- lookup value list = g match
Without thinking too hard, I am curious how anyone could get the meaning of this wrong if they understand the rest of Haskell. Can you show a concrete example, where you think a user would get confused?
sure, the one you gave right there. to be consistent with other uses of '<-' as a generator, I'd expect to write either f value | match <- lookup value list = g match or f value | Just match <- return (lookup value list) = g match Claus

consider the following examples:
-- do-notation: explicit return; explicit guard; monadic result d _ = do { Just b <- return (Just True); guard b; return 42 }
-- list comprehension: explicit return; implicit guard; monadic (list) result lc _ = [ 42 | Just b <- return (Just True), b ]
-- pattern guard: implicit return; implicit guard; non-monadic result pg _ | Just b <- Just True, b = 42
This ongoing discussion has made me curious about whether we could actually get rid of these irregularities in the language, without losing any of the features we like so much. === attempt 1 (a) boolean statements vs guards this looks straightforward. Bool is a type, so can never be an instance of constructor class Monad, so a boolean statement in a monadic context is always invalid at the moment. that means we could simply extend our syntactic sugar to take account of types, and read every ((e :: Bool) :: Monad m => m _) in a statement of a do block as a shorthand for (guard (e :: Bool) :: Monad m => m ()) (b) missing return in pattern guards this could be made to fit the general pattern, if we had (return == id). that would put us into the Identity monad, which seems fine at first, since we only need return, bind, guard, and fail. unfortunately, those are only the requirements for a single pattern guard - to handle not just failure, but also fall-through, we also need mplus. which means that the Identity monad does not have enough structure, we need at least Maybe.. this first attempt leaves us with two problems. not only is (return==id) not sufficient for (b), but the suggested approach to (a) is also not very haskellish: instead of having syntactic sugar depend on type information, the typical haskell approach is to have type-independent sugar that introduces overloaded operations, such as fromInteger :: Num a => Integer -> a to be resolved by the usual type class machinery. addressing these two issues leads us to === attempt 2 (a) overloading Bool following the approach of Num and overloaded numeric literals, we could introduce a type class Boolean class Boolean b where fromBool :: Bool -> b instance Boolean Bool where fromBool = id and implicitly translate every literal expression of type Bool True ~~> fromBool True False ~~> fromBool False now we can embed Boolean statements as monadic statements simply by defining an additional instance instance MonadPlus m => Boolean (m ()) where fromBool = guard (b) adding a strictly matching monadic let we can't just have (return==id), and we do not want the hassle of having to write pattern <- return expr in pattern guards. the alternative of using let doesn't work either let pattern = expr because we do want pattern match failure to abort the pattern guard and lead to overall match failure and fall-through. so what we really seem to want is a shorthand notation for a strict variant of monadic let bindings. apfelmus suggested to use '<=' for this purpose, so that, wherever monadic generators are permitted pattern <= expr ~~> pattern <- return expr === returning to the examples, the approach of attempt 2 would allow us to write -- do-notation: implicit return; implicit guard; monadic result d _ = do { Just b <= Just True; b; return 42 } -- list comprehension: implicit return; implicit guard; monadic (list) result lc _ = [ 42 | Just b <= Just True, b ] -- pattern guard: implicit return; implicit guard; non-monadic result pg _ | Just b <= Just True, b = 42 almost resolving the irregularities, and permitting uniform handling of related syntactic constructs. hooray!-) I say "almost", because Bool permeates large parts of language and libraries, so one would need to check every occurence of the type and possibly replace Bool by (Boolean b => b). the Boolean Bool instance should mean that this process could be incremental (ie, even without replacements, things should still work, with more replacements generalizing more functionality, similar to the Int vs Integer issue), but that hope ought to be tested in practice. one issue arising in practice is that we would like to have fromBool :: MonadPlus m => Bool -> m a but the current definition of guard would fix the type to fromBool :: MonadPlus m => Bool -> m () which would require type annotations for Booleans used as guards. see the attached example for an easy workaround. on the positive side, this approach would not just make pattern guards more regular, but '<=' and 'MonadPlus m => Boolean (m ()) would be useful for monadic code in general. even better than that, those of use doing embedded DSLs in Haskell have been looking for a way to overload Bools for a long time, and the implicit 'Boolean b => fromBool :: Bool -> b' ought to get us started in the right direction. most likely, we would need more Bool-based constructs to be overloaded for Boolean, including at least a function equivalent for if-then-else: class If condition branch where if' :: condition -> branch -> branch -> branch instance If Bool e where if' c t e = if c then t else e instance Monad m => If (m Bool) (m a) where if' c t e = c >>= \b-> if b then t else e with associated desugaring if b then t else e ~~> if' b t e which would also enable us to get around another do notation annoyance, and write things like if (fmap read getLine :: IO Bool) then putStrLn "hi" else putStrLn "ho" all in all, this looks promising, so: thank you, Yitzchak, for insistencing in pointing out the inconsistencies of '<-' (it did cost me some sleep, but I like the results so far!-) I assume there might be downsides as well - any suggestions? Claus

one issue arising in practice is that we would like to have
fromBool :: MonadPlus m => Bool -> m a
but the current definition of guard would fix the type to
fromBool :: MonadPlus m => Bool -> m ()
which would require type annotations for Booleans used as guards. see the attached example for an easy workaround.
what attachment, you ask? sorry, lack of sleep - now attached to this message. claus

apfelmus suggested to use '<=' for this purpose, so that, wherever monadic generators are permitted
pattern <= expr ~~> pattern <- return expr
It was to late when i realized that <= is already used as "smaller than or equal to" :) Obviously, the difference between the pattern guard <- and the monadic <- let easily slips by. I think this has to do with the fact that do-notation is not the natural style for MonadPlus Maybe, the natural style is more like the current syntax of pattern guards. I mean that one rarely hides a Just constructor like in do r <- lookup x map because returning Maybe is a very special case, there are many other constructors to match on where one wants fall-back semantics. Of course, every sum type can be projected to Maybe X =~= X + 1 but this involves boilerplate. In a sense, do-notation is just not appropriate for MonadPlus Maybe. It is somewhat unfortunate that while arrows, monads and pattern guards (= MonadPlus Maybe) could share the same syntax, it is not advisable to do so because this introduces quite annoying boilerplate. The most general syntax is too much for the special case. But there is something more canonical than completely disjoint syntax: in a sense, Claus' suggestions are about making the syntax for the special case a *subset* of the syntax for the more general one. The "partial order of syntax inclusion" should look something like Arrows \ \ MonadPlus \ / Monad Even though arrows are more general than monads (less theorems hold), they require more syntax. On the other hand, MonadPlus provides more than a monad, so it needs a new syntax, too. Remember that these are not the only computation abstractions. Syntactic sugar for pseudo-let-declarations (akin to MonadFix but order independent, can be embedded using observable sharing) is advisable, too. Only applicative functors behave very nicely and fit into current Haskell syntax (maybe that's the reason why they have been discovered only lately? :). In a sense, even ordinary Haskell (= pure functions) is only "syntactic sugar". Some "higher order syntactic sugar" melting machine bringing all these candies together would be very cool. Regards, apfelmus

ooohh.. when I saw the subject, I fully expected a worked out proposal for extensible syntax in Haskell, just in time for Christmas. well, maybe next year!-)
It was to late when i realized that <= is already used as "smaller than or equal to" :)
oops. okay, lets change that. what about this: pattern =< expr ~~> pattern <- return expr a cleaner variant would be a let!, perhaps, but that would probably be too noisy for pattern guards? (also, we don't want to steal nice infix ops like <==)
do-notation is not the natural style for MonadPlus Maybe, the natural style is more like the current syntax of pattern guards. I mean that one rarely hides a Just constructor like in
oh? getting rid of nested (case x of {Just this ->..; Nothing -> that}) is a very good argument in favour of do-notation for Maybe, and I find that very natural (for some definition of nature;-). granted, once one has taken that step, one is close to writing in monadic style anyway, so it is no longer specific which constructors are hidden. but I don't see a specific problem with Maybe there, and I haven't seen convincing sugar for MonadPlus yet.
general syntax is too much for the special case. But there is something more canonical than completely disjoint syntax: in a sense, Claus' suggestions are about making the syntax for the special case a *subset* of the syntax for the more general one.
indeed. thanks for pointing that out. I first went the other direction, but as you say, generalizing pattern guards introduces too much syntax in an awkward place. so my current suggestion follows the subset idea.
Some "higher order syntactic sugar" melting machine bringing all these candies together would be very cool.
hooray for extensional syntax!-) syntax pre-transformation that would allow me to extend a Haskell parser in library code is something I'd really like to see for Haskell, possibly combined with error message post-transformation. together, they'd smooth over the main objections against embedded DSLs, or allow testing small extensions of Haskell. I have been wondering in the past why I do not use Template Haskell more, given that I'm a great fan of meta-programming and reflection, and I think the answer is that it sits in an unfortunate way between two chairs: it cannot quite be used for syntax extensions because it insists on Haskell syntax/scopes/types, and it cannot quite be used as a frontend because there's some typing coming after it. persistent users have found wonderful things to do with it nevertheless, even analysis/ frontend stuff, but its main use seems to be program-dependent program generation, within the limits of Haskell syntax. in fact, I have a pragmatic need for even more, namely type system extensions as well: somewhere on my disk, I have a type-directed monadification prototype, based on a type system that infers not just a type, but a type coercion; works well, at least for simple monomorphic code, but what do I do with it? being type-directed, it uses a completely different foundation than the rest of HaRe refactorings, and to fully realize it for Haskell, I'd have to implement and -here comes the killer- maintain a complete Haskell type system, just because I need a few modifications/extensions. it is just not practical to do so, let alone once for every type-directed algorithm. Claus

... <= is already used as "smaller than or equal to" :)
...what about this: pattern =< expr
... let!, perhaps, but that would probably be too noisy for pattern guards? (also, we don't want to steal nice infix ops like <==)
I had suggested <<- I wouldn't mind <-- or <== or the like. I think any of these better suggest "similiarity to <- yet different". (<= would have been perfect. Humph! They beat us to it.) -Yitz

Claus Reinke wrote:
ooohh.. when I saw the subject, I fully expected a worked out proposal for extensible syntax in Haskell, just in time for Christmas. well, maybe next year!-)
I'm sorry :( But this is because Santa Claus is not yet interested in Haskell: he swears on C-- for writing his high performance "real world" applications used in his Christmas gift delivery company. ;)
I mean that one rarely hides a Just constructor like in
oh? getting rid of nested (case x of {Just this ->..; Nothing -> that}) is a very good argument in favour of do-notation for Maybe, and I find that very natural (for some definition of nature;-).
Ah, I meant it in the sense that Just and Nothing are very special constructors but that this behavior is wanted for other constructors too: data Color a b = Red a | Green a a | Blue b instance MonadPlus (Color a) where ... But now, we are tied again to a specific set of constructors. One might want to have fall-back semantics for any constructor at hand and that's what can be achieved with the "lifted let" (<- return, <<-, <--, <==, let', ...): (Red r <-- x, Left y <-- r, ... ) -- fall-back if anything fails `mplus` (Green g g' <-- x, Just k <-- g, ...) If one wants to hide these things with <- like in the case of Maybe, one would have to project into Maybe: fromRed (Red r) = Just r fromRed _ = Nothing fromBlue (Blue b) = Just b fromBlue _ = Nothing fromGreen (Green g g') = Just (g,g') fromGreen _ = Nothing fromLeft (Left x) = Just x fromLeft _ = Nothing (do r <- fromRed x y <- fromLeft r ...) `mplus` (do (g,g') <- fromGreen x k <- g ...) In this sense, the "lifted let" is more natural for fall-back because it treats all constructors as equal. Maybe just provides the semantics and is to be fused away. So I think that while do-notation is more natural than case-matching for Maybe, the most natural notation for the fall-back semantics are pattern guards. Likewise, list comprehension is the most natural style for (MonadPlus []). Here, one has normal <-, but boolean guards are sugared.
Some "higher order syntactic sugar" melting machine bringing all these candies together would be very cool.
hooray for extensional syntax!-) syntax pre-transformation that would allow me to extend a Haskell parser in library code is something I'd really like to see for Haskell, possibly combined with error message post-transformation. together, they'd smooth over the main objections against embedded DSLs, or allow testing small extensions of Haskell.
Yes, that would be great. But I fear that this will result in dozens of different "Haskell" incarnations, one more obscure than the other. And its completely unclear how different syntax alterations would interoperate with each other.
I have been wondering in the past why I do not use Template Haskell more, [...]but its main use seems to be program-dependent program generation, within the limits of Haskell syntax.
True. Compared to Template Haskell, a preprocessor allows syntactic extensions but is weak at type correctness. Regards, apfelmus

Iavor Diatchki wrote:
I am not clear why you think the current notation is confusing... Could you give a concrete example? I am thinking of something along the lines: based on how "<-" works in list comprehensions and the do notation, I would expect that pattern guards do XXX but instead, they confusingly do YYY. I think that this will help us keep the discussion concrete.
Pattern guards basically are a special-case syntactic sugar for (instance MonadPlus Maybe). The guard foo m x | empty m = bar | Just r <- lookup x m, r == 'a' = foobar directly translates to foo m x = fromMaybe $ (do { guard (empty m); return bar;}) `mplus` (do {Just r <- return (lookup m x); guard (r == 'a'); return foobar;}) The point is that the pattern guard notation Just r <- lookup m x does *not* translate to itself but to Just r <- return (lookup m x) in the monad. The <- in the pattern guard is a simple let binding. There is no monadic action on the right hand side of <- in the pattern guard. Here, things get even more confused because (lookup m x) is itself a Maybe type, so the best translation into (MonadPlus Maybe) actually would be r <- lookup m x Regards, apfelmus

Yitzchak Gale writes:
Philippa Cowderoy wrote:
I don't find it any more confusing than the overloading of ->.
I wrote:
You mean that it is used both for lambda abstractions and for functional dependencies? True, but those are so different that there is no confusion.
Oh, and case. Also quite different.
Also type and kind signatures.
The use in case and lambda abstractions strike me as analogous. They
both have a pattern to the left and an expression to the right.
--
David Menendez

On Wed, 13 Dec 2006, Yitzchak Gale wrote:
Yitzchak Gale wrote:
Of course, this is not really the joy of pattern guards. It is the joy of monads, with perhaps a few character strokes saved by a confusing overloading of (<-).
Philippa Cowderoy wrote:
I don't find it any more confusing than the overloading of ->.
You mean that it is used both for lambda abstractions and for functional dependencies? True, but those are so different that there is no confusion.
You missed out case statements. -- flippa@flippac.org "My religion says so" explains your beliefs. But it doesn't explain why I should hold them as well, let alone be restricted by them.
participants (10)
-
apfelmus@quantentunnel.de
-
Claus Reinke
-
Dave Menendez
-
dons@cse.unsw.edu.au
-
Iavor Diatchki
-
mm
-
Neil Mitchell
-
Philippa Cowderoy
-
Yitz Gale
-
Yitzchak Gale