proposal: introduce lambda-match (explicit match failure and fall-through)

name: introduce lambda-match (explicit match failure and fall-through) summary: Haskell 98 provides *two different translations* of lambda abstractions involving pattern matching, only one of which is directly accessible (Section 3.3 - the other is embedded in the translation of do-notation, see "ok" in Section 3.14). providing explicit source notation for the second translation, substantially simplifies programmability of pattern-match fall-through by reification of pattern-match failure, two central language features that are so far only available through the built-in, non-composable case construct. what: in Section 3.3, the translation for conventional lambda abstractions with patterns is given as [| \p1 .. pn-> e |] = \x1 .. xn-> case (x1,..,xn) of (p1,..,pn) -> e with xi fresh identifiers, and pattern-match failure resulting in _|_. the latter is unfortunate, and results in partial functions the coverage of which cannot be combined, but it is forced by translation into conventional lambda calculus. since computational lambda calculus (\-M) has become a central part of Haskell programming practice, there shall be an alternative form of lambda abstraction, dubbed here lambda-match, with associated translation into \-M: [| |p1 .. pn-> e |] = \x1 .. xn-> case (x1,..,xn) of { (p1,..,pn) -> return e; _ -> fail "no match" } [note1: this is the translation in principle - in practice, to enable composition of lambda-matches without further language extensions, a slight modification is needed, wrapping the right-hand sides of the case in a Match constructor, see library and patch] a library for composing these lambda-matches shall provide for composition of alternative lambda-matches (+++), match failure (nomatch) and embedding of the explicit match monad into pure expressions (splice, where "splice |p1..pn->e = \p1..pn->e"). [note2: an alternative translation would use do-notation instead of case as the target: [| |p1 .. pn-> e |] = \x1 .. xn-> do { (p1,..,pn) <- return (x1,..,xn); return e } both translations easily accomodate guards and pattern guards as well, the former by building on existing support for these two features in case constructs, the latter without requiring any previous implementation of pattern guards, by lifting (pattern) guards into the match monad] implementation impact: minimal - limited to an extension in parser/desugarer, employing previously inaccessible syntax for lambda-match, and a slight variation of the existing lambda translation; also adds a small library to support composition of matches. [note3: a first draft of the composition library and a patch for GHC (about a dozen new lines in the parser) are provided as attachments to this proposal, together with some examples] context: as has been pointed out in the thread on replacing and improving pattern guards, Haskell's pattern matching support, even before pattern guards, is monolithic (built-in case is the only way to handle multiple alternative matches) rather than compositional (lambdas represent individual alternatives, but cannot be composed on match fall-through). this implies increased complexity of the language definition and limited expressiveness of its features, when compared with alternative models (eg, adapting Wolfram's pattern match calculus for Haskell). see, eg.: http://www.haskell.org/pipermail/haskell-prime/2006-October/001713.html http://www.haskell.org/pipermail/haskell-prime/2006-October/001720.html http://www.haskell.org/pipermail/haskell-prime/2006-October/001723.html http://www.haskell.org/pipermail/haskell-prime/2006-October/001724.html in principle, replacing Haskell's current pattern matching support with a simpler, more compositional model, and defining the current constructs on top of that new core is the way forward, IMHO. in practice, however, I suspect that the committee is less than tempted to introduce such a substantial simplification for Haskell'. the present proposal is an attempt at a compromise, suggesting a minimal language change to introduce compositional pattern-match failure and fall-through. with lambda-match, it implements only a single language extension (as syntactic sugar), delegating the rest of the functionality to a library. without the sugar, the result of the by-hand translation becomes so hard to read as to be near unusable, while the chosen form of sugaring allows to provide most of the language features discussed in the earlier threads to be provided as a library. this does seem to be a useable balance. building constructs of the simpler pattern-match model on top of the more complex one is somewhat irksome from a language design perspective, but does at least gain the expressiveness of the simpler model. if programmers make substantial use of this new functionality in Haskell' (as I strongly suspect they will - I have been doing similar translations by hand for some time now), it will be up to Haskell'' to turn the table, and to define the current complex model on top of a compositional one. as a preview of this anticipated language refactoring;), it is instructive to compare the two alternative translations of lambda-match sketched above: - the first directly builds on the existing, complex case constructs with their built-in (pattern) guards and match fall-through support; this eases adding the new, simpler features to implementations that support the old, complex ones (like GHC), but completely foregoes any attempt to simplify those implementations in the process; [the attached patch for GHC follows this route] - the second translation avoids any direct reference to case, employing do-notation instead; this requires slightly more effort, eg. in translating pattern guards into the match monad, but is eminently suitable for adding the new features to implementations that do not support pattern guards yet, or that simply want to reduce the number of built-in constructs. [patchers for Hugs, etc., might want to follow this route?]

name: introduce lambda-match (explicit match failure and fall-through)
Dear All, may I be so optimistic as to interpret the absolute lack of counter arguments over the last week as indication that this proposal is acceptable in general? Thanks to those few who have expressed support so far, usually in the form "I've wanted something like this for years"! (*) I have braved the evil trac-wiki formatter again, to convert the email proposal into a slightly updated ticket, with attached patch for GHC, support libraries and usage examples: introduce lambda-match (explicit match failure and fall-through) http://hackage.haskell.org/trac/haskell-prime/ticket/114 most notable updates are in the support library (now being a bit more helpful in preserving error messages and defining fall_through cases; also supports joining of nested matches now), with a few added examples demonstrating the changes. It is a good sign that the syntax patch itself has not changed so far, and the support library now supports most of what I had in mind for it (took me a while to figure out how to do "nest" ;-). But it would be very helpful if more eyes looked over the code, to see if the functionality is roughly right (not to mention the implementation). And, of course, syntax patches for other Haskell implementations would be great (at least verify whether your favourite implementation can handle the support library, please - so far verified for GHC and Hugs)! Thank you, Claus ps. a quick recap for those who don't read webpages: a lambda-match | <patterns> | <guards> -> <expr> is syntactic sugar for \ <parameters> -> case <parameters> of { <patterns> | <guards> -> Match $ return <expr> ; _ -> Match $ fail "lambda-match failure" } which allows us to program explicitly with match failure (represented as Monad.fail/MonadPlus.mzero) and match fall-through (using MonadPlus.mplus), lifting MonadPlus operations over function parameters for ease of use. this enables us to write previously practically impossible things (the example file gives some indication of just how unreadable and hence unusable these would be without syntactic sugar), such as a user-defined case-variant (included in the library): caseOf True $ ( |True-> False ) +++ ( |False-> True ) --> False or monadic match-failure without using do-notation: return True >>= (ok $ |False-> return "hi") :: Maybe String --> Nothing lambda-matches may be nested, but unlike PMC, that will usually result in nested match monads, unless we use the new "nest" to join the nested monads: myAnd = splice (nest (|True-> (|True->True) +++ (|False->False)) +++ nest (|False-> fall_through False) ) we can now also abstract over groups of match alternatives: grp :: MonadPlus m => String -> [(String, String)] -> Match m String grp = (| x locals | Just y <- lookup x locals -> y) +++ (| "X" locals -> "42") +++ matchError "var not found" and extend them later, or just use them to build different functions: -- select only the first match varVal :: String -> [(String, String)] -> String varVal = spliceE grp -- a variation, delivering all successful matches varVals :: String -> [(String, String)] -> [] String varVals = allMatches grp leading to uses like these: *Main> varVal "X" [("X","hi")] "hi" *Main> varVal "Z" [("X","hi")] "*** Exception: var not found *Main> varVals "X" [("X","hi")] ["hi","42"] *Main> varVals "Z" [("X","hi")] [] and so on, and so on.. see the proposal attachments for more inspirations !-) (*) it might be useful for the Haskell' committee to clarify the process for acceptance of proposals, similar to what the Haskell library community has done recently: http://haskell.org/haskellwiki/Library_submissions (where the intent of the discussion period is to focus the process, and to ensure progress, ie lack of objections to a clearly implementable/implemented proposal is seen as implicit agreement)

Claus Reinke writes:
may I be so optimistic as to interpret the absolute lack of counter arguments over the last week as indication that this proposal is acceptable in general?
Since we don't have any experience of using this extension, and it comes late in the day, it's highly unlikely to become a part of Haskell', simply because the stated mission of Haskell' is to solidify the tried-and-trusted extensions. Cheers, Simon
Thanks to those few who have expressed support so far, usually in the form "I've wanted something like this for years"! (*)
I have braved the evil trac-wiki formatter again, to convert the email proposal into a slightly updated ticket, with attached patch for GHC, support libraries and usage examples:
introduce lambda-match (explicit match failure and fall-through) http://hackage.haskell.org/trac/haskell-prime/ticket/114
most notable updates are in the support library (now being a bit more helpful in preserving error messages and defining fall_through cases; also supports joining of nested matches now), with a few added examples demonstrating the changes.
It is a good sign that the syntax patch itself has not changed so far, and the support library now supports most of what I had in mind for it (took me a while to figure out how to do "nest" ;-). But it would be very helpful if more eyes looked over the code, to see if the functionality is roughly right (not to mention the implementation).
And, of course, syntax patches for other Haskell implementations would be great (at least verify whether your favourite implementation can handle the support library, please - so far verified for GHC and Hugs)!
Thank you, Claus
ps. a quick recap for those who don't read webpages: a lambda-match
| <patterns> | <guards> -> <expr>
is syntactic sugar for
\ <parameters> -> case <parameters> of { <patterns> | <guards> -> Match $ return <expr> ; _ -> Match $ fail "lambda-match failure" }
which allows us to program explicitly with match failure (represented as Monad.fail/MonadPlus.mzero) and match fall-through (using MonadPlus.mplus), lifting MonadPlus operations over function parameters for ease of use.
this enables us to write previously practically impossible things (the example file gives some indication of just how unreadable and hence unusable these would be without syntactic sugar), such as a user-defined case-variant (included in the library):
caseOf True $ ( |True-> False ) +++ ( |False-> True ) --> False
or monadic match-failure without using do-notation:
return True >>= (ok $ |False-> return "hi") :: Maybe String --> Nothing
lambda-matches may be nested, but unlike PMC, that will usually result in nested match monads, unless we use the new "nest" to join the nested monads:
myAnd = splice (nest (|True-> (|True->True) +++ (|False->False)) +++ nest (|False-> fall_through False) )
we can now also abstract over groups of match alternatives:
grp :: MonadPlus m => String -> [(String, String)] -> Match m String grp = (| x locals | Just y <- lookup x locals -> y) +++ (| "X" locals -> "42") +++ matchError "var not found"
and extend them later, or just use them to build different functions:
-- select only the first match varVal :: String -> [(String, String)] -> String varVal = spliceE grp
-- a variation, delivering all successful matches varVals :: String -> [(String, String)] -> [] String varVals = allMatches grp
leading to uses like these:
*Main> varVal "X" [("X","hi")] "hi" *Main> varVal "Z" [("X","hi")] "*** Exception: var not found *Main> varVals "X" [("X","hi")] ["hi","42"] *Main> varVals "Z" [("X","hi")] []
and so on, and so on.. see the proposal attachments for more inspirations !-)
(*) it might be useful for the Haskell' committee to clarify the process for acceptance of proposals, similar to what the Haskell library community has done recently:
http://haskell.org/haskellwiki/Library_submissions
(where the intent of the discussion period is to focus the process, and to ensure progress, ie lack of objections to a clearly implementable/implemented proposal is seen as implicit agreement)
_______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime

Some of you have asked me whether I could provide more convincing examples for lambda-match, or whether the shortcomings of Haskell addressed in this proposal will be of practical relevance to the typical seasoned Haskeller without specific interests in language design. There are of course the various themes of views, pattern abstractions, and first-class patterns, which could be built on top of lambda-match, but I'd like to follow a slightly different angle first, inspired by an interesting off-list remark in response to the lambda-match proposal: I do consider myself a fairly seasoned Haskell programmer, and to be honest, I have to admit that I rarely if ever have missed composable pattern matching at the source level. Of course, that could be because I subconsciously just work around the problem, being used to Haskell as it is. I do indeed believe that the problem of non-compositional pattern match has been around in Haskell for so long that many of today's Haskellers are no longer even aware of the issue, and of how much it affects them. So, here is one slightly less trivial example of using lambda-match, which happens to stand for a large group of possible applications, and for one particular area where the lack of compositional patterns has influenced the Haskeller's world-view: Ever since I took up Haskell, I have wondered why Haskellers tend to specify their grammars not just twice (abstract + concrete), but thrice (abstract + parsing + unparsing). The majority of seasoned Haskellers seems to accept that there must be parsers+pretty-printers, read+show, serialize+de-serialize, etc., and that changing concrete syntax must involve making fixes in two separate bits of code, often even following two separate coding patterns. But if one looks at so-called parser combinators, there is very little in them that is parser-specific - usually only the literal parsers determine that we are talking about parsing, whereas the majority of combinators can be used just as well for other syntax-directed tasks. Still, people tend not to reuse their combinator-based grammars for anything but parsing. I submit that one of the main reasons for this is that Haskellers have come to accept that they can construct, but not deconstruct algebraic types in a compositional way (hence the use of parser combinators for converting Strings into algebraic data types, and the use of more pedestrian means for showing the latter as Strings; pretty-printing libraries do at least use combinators, but do not reuse the grammars specified through parser combinators). Please have a look at the example (which needs both syntax patch and library from the proposal ticket, if you actually want to run it *, but the ideas should be reasonably obvious even without): it specifies a concrete and abstract syntax for lambda calculus, and the relationships between the two levels of syntax, using an algebraic data type for the abstract syntax, and a grammar built with monadic combinators for the rest. fairly standard, but for the following: language and library support for monadic data parsing via lambda-match allow us to mix data parsing and string parsing in the same monadic framework, using the same "grammar combinators" to specify the concrete syntax and its relation to the abstract syntax just once, in one piece of code. we can use that single grammar for parsing, unparsing, or indeed, for mixtures of both (see the examples). A long time ago, I used something like this (then sadly without language support) to implement a syntax-oriented editor, with parsing and formatted printing from a single grammar. Although I haven't worked this out, I suspect that the technique would also apply to protocol-based applications: instead of writing client and server separately (and then trying to prove that they fit together and follow two sides of the same protocol), one might try to write a single grammar for the protocol between them, toggling mode at the appropriate points, and then client and server would simply be two instances/uses of the same grammar in its two start modes (so the server would generate prompts, parse requests, and generate responses, and the client would expect prompts, generate requests, and parse responses). have fun;-) claus * I have submitted the syntax patch for the GHC head repository, * but GHC HQ are reluctant to apply the patch as long as there * is no obvious general interest (someone else but myself, and * not just in private email to myself;-) in using these features. If * you want to investigate lambda-match in GHC, to make up your * mind about whether or not you like the proposal (at the moment, * we're only talking about the daily snapshots of GHC head, not * about long-term support in GHC, let alone inclusion in Haskell'!), * please let yourself be heard! (more adventurous souls can of course apply the patch from the ticket themselves and recompile GHC;-) I have also updated the proposal ticket with a list of motivation bullet-points for lambda-match: http://hackage.haskell.org/trac/haskell-prime/ticket/114

in earlier examples, we have seen how a monadic data parsing framework allows us to move from built-in case constructs to composable match alternatives, where the alternatives are represented by lambda-matches; we have then seen how this enables us, eg., to combine data parsing and string parsing to specify parsers and unparsers by the same combinator grammar. this, probably the final example in this series, is rather more speculative, showing a sketch of moving beyond composable match alternatives, to composable patterns (aka pattern abstractions, views, first-class patterns, ..). we can use the same monadic data parsing framework, but if we want to avoid further syntactic sugar, we either have to abandon pattern variables, or we have to play some tricks. the attached files outline - a sketch of a simple pattern library supporting pattern variables, as-patterns, wildcards and composable match rules (single argument match rules only here) - as an example of using this pattern library, a user-defined array-based list type, with user-defined pattern constructors (cons and snoc views) [the type is not all that interesting in itself, I just needed an example that didn't already come with algebraic data constructors/patterns] it is also vaguely related to ByteString, so you could define pattern constructors for that as well (*after* expanding this sketch of a pattern library into a somewhat safer version, of course!-) using the pattern library, match rules generally look like this: (lhs ==> rhs) and are composed using the usual lambda-match combinators splice $ (lhs1 ==> rhs1) +++ ... +++ (lhsN ==> rhsN) if a match rule involves pattern variables, it'll look like this: (vV $ \v1..vn-> Vv $ lhs ==> rhs) where a pattern variable v may be bound in lhs using (v|!), and refered to in rhs using (v|?). this pattern-variable workaround avoids syntactic sugar ("look, ma! first-class patterns with variables, without sugar!":-), but makes match rules look more clumsy (also, no attempt has been made (yet) to safeguard these variable accesses). since we define all our own patterns here, this example doesn't need the syntax patch for lambda-match, only the lambda-match libraries (I've tested it in Hugs) - in fact, the main purpose of that syntax patch is to incorporate all the work invested in conventional matches into the monadic data parsing framework (have I now mentioned this terminology often enough?-). enjoy (and let me know if I have convinced any more of you!-) Claus ps GHC HQ have agreed to incorporate the lambda-match syntax patch, once I extend it with documentation and test cases; so that is good news; I guess the next step after that will be to pitch the support library to the libraries list, and perhaps to get Hugs and others to follow suit wrt the syntax patch. to avoid confusion: nothing in this example email is part of my Haskell' proposal, it is just a motivating example showing what could be built on top of lambda-match in the future. I do hope it'll help to convince people that lambda-match itself is not just a trivial clean-up of the language report or an odd way to write patterns, but an interesting lever and point of entry into the exciting world of composable matches and monadic data parsing (there, I said it again!-).
participants (2)
-
Claus Reinke
-
Simon Marlow