[Haskell] Views in Haskell
 
            Sorry to enter the discussion a little late ... First, I'm not clear what Simon meant by "first class abstractions" in this comment
Several proposals suggest first class abstractions rather that first-class patterns. Here are the ones I know of ...
Second, I completely agree with Claus in his comment here that my "First Class Patterns" paper is definitely related to, and not orthogonal to view patterns: The "big idea" of my paper was to stop the growing complexity of the pattern-language of Haskell. The idea was to use the abstraction capabilities of the language along with some simple syntactic sugar to give us 'pattern omnipotence'. However, my approach could be seen as orthogonal in that I did not propose to change Haskell patterns. Instead, I suggested some additional syntax that could serve as a replacement for complicated uses of patterns. Strangely, for other reasons, I'm planning, within a week or so, to start implementing the "pattern-binder" syntax I discussed in the paper (either in GHC or as a pre-processor). - Mark Claus Reinke wrote:
3 what you call first class abstractions are not entirely orthogonal to view patterns. taking Tullsen's and my own proposal as examples:
- the way patterns and alternatives are handled needs to fit together. that doesn't seem to be a problem since your and our proposals agree on using what I call a monadic data parsing framework (using a MonadPlus such as Maybe to handle pattern match failure and alternatives)
- all three proposals have discussed how to handle patterns as well. For Tullsen, that is central to his proposal, for me, it was only one of the more advanced examples because I wanted to focus on match alternatives first.
Tullsen first builds his pattern combinators, then outlines a point-free style that avoids the need for pattern variables althogether but does not seem to scale well, then suggests syntactic sugar for translating patterns with variables into applications of his combinators. So that last part is closely related to, if different from, your proposal.
In my example, I build up patterns from de-constructors (which use tests and selectors), so that a cons pattern takes a head pattern and a tail pattern as parameters and applies them to the head and tail if it is applied to a non-empty list. To handle variables, I use an old trick from the early functional logic languages, namely that logic variables can be passed unbound, then bound to values later, just what we need for pattern variables. Since Haskell doesn't have logic variables, I have to simulate them, which is the only awkward bit of the example: http://www.haskell.org/pipermail/haskell-prime/2006-November/ 001915.html
as long as Haskell doesn't support logic variables, some syntactic sugar for variables in nested patterns, such as Tullsen's or your's, is probably inevitable.
 
            | First, I'm not clear what Simon meant by "first class abstractions" | in this comment | | > Several proposals suggest first class abstractions rather that | > first-class patterns. Here are the ones I know of ... Sorry to have been un-clear. By a "first class abstraction" I mean a value of type something -> something with a syntax something like \ pattern -> body The abstraction includes both the pattern and the result. In contrast, view patterns tackle only the syntax of patterns; the pattern of a first-class abstraction. I'll update the wiki A first-class *pattern*, on the other hand, really ought to be something like (a,b), where a and b are *binders*. This is what Barry Jay means by a first-class pattern in his very interesting work (which I should reference from the wiki). See "The Patten Calculus" http://www-staff.it.uts.edu.au/~cbj/Publications/chronological.html Still, I think it's likely that I'm exaggerating, and that view patterns and first-class abstractions are tied up together somehow. But I don't grok exactly how. Simon
 
            Strangely, for other reasons, I'm planning, within a week or so, to start implementing the "pattern-binder" syntax I discussed in the paper (either in GHC or as a pre-processor).
I'm somewhat surprised to read this. Between view patterns, lambda-match, and Control.Monad.Match, I thought we were approaching a situation in which we have all the essential aspects covered (perhaps apart from the fact that your combinators come in both left-right and right-left variants), with slightly more convenience and better integration with existing pattern match facilities Especially the pattern-binder syntax and translation strike me as more complicated (so much so that I would rather use a simplified form of the translation result than all that machinery) and no more general than combining view patterns with pattern functions. But perhaps that is a question of personal style (and my own use of type-classes to lift mplus to pattern-functions has also been classed as complicated by others;-). Is there anything specific you find missing, or a those other reasons the motivation with going for your own version? Claus
 
            On Jan 25, 2007, at 6:40 AM, Claus Reinke wrote:
Strangely, for other reasons, I'm planning, within a week or so, to start implementing the "pattern-binder" syntax I discussed in the paper (either in GHC or as a pre-processor).
I'm somewhat surprised to read this. Between view patterns, lambda- match, and Control.Monad.Match, I thought we were approaching a situation in which we have all the essential aspects covered (perhaps apart from the fact that your combinators come in both left-right and right- left variants), with slightly more convenience and better integration with existing pattern match facilities Especially the pattern-binder syntax and translation strike me as more complicated (so much so that I would rather use a simplified form of the translation result than all that machinery) and no more general than combining view patterns with pattern functions. But perhaps that is a question of personal style (and my own use of type-classes to lift mplus to pattern-functions has also been classed as complicated by others;-).
Is there anything specific you find missing, or a those other reasons the motivation with going for your own version?
Claus
Good question. It's not that I think there is some "essential aspect" which isn't covered: View patterns will definitely add some useful expressiveness, and ditto for lambda-match and Control.Monad.Match (though I haven't yet had time to fully assimilate this stuff: I didn't start following this thread till yesterday). First Class Patterns are radical enough and are so far from meshing with the pattern language of Haskell that I don't really consider them a "competing proposal". My motivations for implementing "pattern-binder" syntax are as follows 1) I have a special need for some significant syntactic sugar for which pattern binders perfectly fit the bill. (For general programming I use my pattern combinators and the 'do' notation.) 2) There are other reasons why I want to use Haskell-98 and would like to be able to use other compilers. Thus, I'd want a pattern-binder preprocessor (extending GHC is not as important to me). Here's my motivating example. Here's a fragment for an STG interpreter in Haskell-98: {{{ rule_CASE_ELIM (Case p alts, s, h, o) = do ConApp c as <- ptsTo p h let matchAlt (Alt c' vs e) | c == c' = Just (vs,e) matchAlt _ = Nothing (vs,e) <- matchFirst matchAlt alts return (e `sub` (vs,as), s, h, o) }}} I'd like it to have a textual form just a little more abstract, I can do that with pattern binders and some appropriate combinators: {{{ rule_CASE_ELIM = { (Case p alts , s, h, o) } &&& ptsTo p h === { ConApp c as } &&& alts === matchFirst { Alt #c vs e } .-> (e `sub` (vs,as), s, h, o) }}} I'll leave it as an exercise to figure out how the last is parenthesized ;-). - Mark
 
            2) There are other reasons why I want to use Haskell-98 and would like to be able to use other compilers. Thus, I'd want a pattern-binder preprocessor (extending GHC is not as important to me).
I see. though I'd hope that as long as we keep our extensions simple and general enough, the other implementations will pick them up anyway.
Here's my motivating example. Here's a fragment for an STG interpreter in Haskell-98: {{{ rule_CASE_ELIM (Case p alts, s, h, o) = do ConApp c as <- ptsTo p h let matchAlt (Alt c' vs e) | c == c' = Just (vs,e) matchAlt _ = Nothing (vs,e) <- matchFirst matchAlt alts return (e `sub` (vs,as), s, h, o) }}}
yes, abstract machines have inspired many a pattern match extension!-) are we in Maybe, or in anything more complex? view patterns don't seem to apply, but pattern guards do, and lambda-match helps with the local function pattern (ignoring the Match type tag for the moment; given the revival of interest in pattern functions, eg., in view patterns, I ought to try and see whether I can get rid of the type tag in my library for the special case of Maybe): {{{ rule_CASE_ELIM = (| (Case p alts, s, h, o) | ConApp c as <- ptsTo p h , (vs,e) <- matchFirst (| (Alt c' vs e) | c == c' ->(vs,e) ) alts -> (e `sub` (vs,as), s, h, o) ) }}} which isn't quite as abstract as the pattern binder/combinator version, but at least I can see the scoping, which I am at a loss with in the pattern binder version:
I'd like it to have a textual form just a little more abstract, I can do that with pattern binders and some appropriate combinators:
{{{ rule_CASE_ELIM = { (Case p alts , s, h, o) } &&& ptsTo p h === { ConApp c as } &&& alts === matchFirst { Alt #c vs e } .-> (e `sub` (vs,as), s, h, o) }}}
I'll leave it as an exercise to figure out how the last is parenthesized ;-).
ok, I give up. there seem to be some new combinators, and the pattern binder variables are no longer distinguishable (via $). but unless you've changed the translation as well, the only way the scopes are going to come out right is if the layout is a lie, right? and how does the translation apply to pattern binders not in an infix application, in particular, how do vs/e get to the rhs of .->? Claus
 
            On Jan 26, 2007, at 6:22 PM, Claus Reinke wrote:
2) There are other reasons why I want to use Haskell-98 and would like to be able to use other compilers. Thus, I'd want a pattern-binder preprocessor (extending GHC is not as important to me).
I see. though I'd hope that as long as we keep our extensions simple and general enough, the other implementations will pick them up anyway.
Here's my motivating example. Here's a fragment for an STG interpreter in Haskell-98: {{{ rule_CASE_ELIM (Case p alts, s, h, o) = do ConApp c as <- ptsTo p h let matchAlt (Alt c' vs e) | c == c' = Just (vs,e) matchAlt _ = Nothing (vs,e) <- matchFirst matchAlt alts return (e `sub` (vs,as), s, h, o) }}}
yes, abstract machines have inspired many a pattern match extension!-)
are we in Maybe, or in anything more complex?
Yep, just Maybe.
view patterns don't seem to apply, but pattern guards do, and lambda-match helps with the local function pattern (ignoring the Match type tag for the moment; given the revival of interest in pattern functions, eg., in view patterns, I ought to try and see whether I can get rid of the type tag in my library for the special case of Maybe):
{{{ rule_CASE_ELIM = (| (Case p alts, s, h, o) | ConApp c as <- ptsTo p h , (vs,e) <- matchFirst (| (Alt c' vs e) | c == c' ->(vs,e) ) alts -> (e `sub` (vs,as), s, h, o) ) }}}
which isn't quite as abstract as the pattern binder/combinator version, but at least I can see the scoping,
Thanks for showing how it looks with lambda-match, I see that lambda- matches use more than patterns, they use guards too.
which I am at a loss with in the pattern binder version:
I'd like it to have a textual form just a little more abstract, I can do that with pattern binders and some appropriate combinators: {{{ rule_CASE_ELIM = { (Case p alts , s, h, o) } &&& ptsTo p h === { ConApp c as } &&& alts === matchFirst { Alt #c vs e } .-> (e `sub` (vs,as), s, h, o) }}} I'll leave it as an exercise to figure out how the last is parenthesized ;-).
ok, I give up. there seem to be some new combinators,
yes, but nothing fancy: (&&&) :: (a -> Maybe b) -> (b -> Maybe c) -> a -> Maybe c (&&&) = (.:) -- as in the paper (===) :: a -> (a -> Maybe b) -> Maybe b (===) a p = p a
and the pattern binder variables are no longer distinguishable (via $).
In this example I'm dropping the $: it's less clear what's going on but it looks cleaner, more like Haskell patterns.
but unless you've changed the translation as well, the only way the scopes are going to come out right is if the layout is a lie, right?
The layout /is/ a lie :-( but the scope rule is pretty simple: in this expression {p} `op` e everything bound in p scopes over all e. So, all the variables in the {p}'s above scope to the end of the RHS expression.
and how does the translation apply to pattern binders not in an infix application, in particular, how do vs/e get to the rhs of .->?
Claus
All the pattern binders here /are/ in an infix application, here's the parenthesized version: {{{ rule_CASE_ELIM = { (Case p alts , s, h, o) } &&& (ptsTo p h ==> { ConApp c as } &&& (alts === (matchFirst ({ Alt #c vs e } .-> (e `sub` (vs,as), s, h, o))))) }}} (Oops, I see I'm using # where in the paper I used "=".) I also fixed a type error (nothing like ghci to fix some design problems), I'm now using an additional (rather simple) combinator: (==>) :: Maybe a -> (a -> Maybe b) -> Maybe b (==>) = (>>=) - Mark
participants (3)
- 
                 Claus Reinke Claus Reinke
- 
                 Mark Tullsen Mark Tullsen
- 
                 Simon Peyton-Jones Simon Peyton-Jones