
http://hackage.haskell.org/trac/haskell-prime/wiki/ViewPatterns
I'm thinking of implementing it in GHC, so I'd be interested in feedback of the form - how desirable is it to have a feature of this general form? - can this particular proposal be improved?
IMHO, getting a handle on the ADT vs pattern matching issues is overdue, so thanks for raising this again. a few first comments: 1 I am a bit concerned about the use of non-linear patterns in your examples. There are good arguments for non-linear patterns, and Haskellers have made good arguments against non-linear patterns. But you seem to suggest allowing non-linear patterns in some cases (related to view patterns), but not in others (general patterns). That is likely to be confusing. 2 view patterns nicely separate expressions in patterns from pattern variables. But I didn't realize at first that view patterns can be used nested inside other patterns. Yet this variable binding during nested matching is the essential contribution, and the only reason why the extra syntactic sugar is justified. Perhaps this point could be repeated and emphasized in "The proposal more formally", for people like me?-) 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. 4 whether to use view patterns inside ordinary patterns, or whether to build up patterns from abstract de-constructors (just as expressions are built from abstract constructors) may seem only a question of style. but if your aim is to encourage people to transition from exporting concrete data types to exporting abstract types only, the latter approach seems more consistent to me. In my example, a cons de-constructor would be as simple as -- the cons view of array lists is a higher-order pattern that takes -- patterns for the head and tail components, and applies them after -- checking whether the list parameter is a non-empty list consAP h t l = do { Match $ guard $ not (isNilA l); h (headA l); t (tailA l) } but that relies on the scoping of (simulated) logic variables, and it does not translate directly to your view patterns, as the h and t pattern parameters would have their own scope for their pattern variables. It would be instructive to have something equivalent to pattern constructors/abstract deconstructors for view patterns, if only to see whether view patterns can support a fully abstract style of nested matches easily. I am not entirely sure they do, but here is a first attempt: -- abstract list deconstructors / list pattern constructors -- (consP takes h/t sub-patterns as parameters) consP h t l = do { guard $ not (null l); hr <- h (head l); tr <- t (tail l); return (hr,tr) } nilP l = do { guard $ null l; return () } -- wildcard and variable patterns wildP l = return () varP = return -- extract the head of the tail of the parameter list, if that list has two elements f (consP wildP (consP varP nilP) -> (_,(x,_))) = x It seems a bit awkward to have to specify the structure of the parameter twice, once to build up the pattern, then again to match sub-expressions to variables. but would this work in principle at least? 5 possible extension 1 smells of superfluous complexity. There is almost no gain compared to using tuples, but there's a lot to pay in added types and rules. 6 possible extension 2 seems a non-starter if we want compositional abstract patterns, and I certainly do want them. Imagine the example in (4) with explicit Maybe. Being able to have compositional abstract patterns would be the make-or-break criterion for me. Without them, new syntactic sugar wouldn't be justified, with them, their precise form is a matter of convenience. Claus

-- abstract list deconstructors / list pattern constructors -- (consP takes h/t sub-patterns as parameters) consP h t l = do { guard $ not (null l); hr <- h (head l); tr <- t (tail l); return (hr,tr) } nilP l = do { guard $ null l; return () }
-- wildcard and variable patterns wildP l = return () varP = return
-- extract the head of the tail of the parameter list, if that list has two elements f (consP wildP (consP varP nilP) -> (_,(x,_))) = x
hmm, the above was probably guided too much by thinking about my own proposal (and this style could be translated back to it fairly easily, I think). the following would make better use of view patterns, and be a lot simpler: -- cons pattern/deconstructor consP l = do { guard $ not (null l); return (head l, tail l) } -- extract head of tail of two-element list f (consP -> (_, consP -> (x, []) ) ) = x btw, lambda-match and view patterns complement each other: - the sugar in lambda-match embeds classical matches in data parsing - the sugar in view patterns embeds data parsing in classical patterns In view of this, I was wondering: if you do not limit yourself to Maybe, but allow other MonadPlus instances, wouldn't that give you or-patterns? also, view patterns give us local guards: g ( xs@( guard . not . null -> () ) ) ys = xs++ys if we combine these two, we could presumably do things like using the list MonadPlus for backtracking matches, as proposed in some other functional languages (also assuming non-linearity of patterns here): select :: Eq a => a -> Map a b -> b select key ( toList -> ( (guard . (key==) ) ,value) ) = value claus

| 1 I am a bit concerned about the use of non-linear patterns in your examples. | There are good arguments for non-linear patterns, and Haskellers have made good | arguments against non-linear patterns. But you seem to suggest allowing non-linear | patterns in some cases (related to view patterns), but not in others (general patterns). | That is likely to be confusing. I don't think view patterns are non-linear at all! They are just as linear as Haskell's existing patterns. Definitely no implicit use of equality, for example. | 2 view patterns nicely separate expressions in patterns from pattern variables. But I | didn't realize at first that view patterns can be used nested inside other patterns. | | Yet this variable binding during nested matching is the essential contribution, and | the only reason why the extra syntactic sugar is justified. Perhaps this point could | be repeated and emphasized in "The proposal more formally", for people like me?-) I've added a section called "Nesting". You can readily edit it (since I moved the page) to amplify if you think it would help. | 3 what you call first class abstractions are not entirely orthogonal to view patterns. | taking Tullsen's and my own proposal as examples: I'm afraid I don't follow this. I think they are entirely orthogonal. | 4 whether to use view patterns inside ordinary patterns, or whether to build up | patterns from abstract de-constructors (just as expressions are built from | abstract constructors) may seem only a question of style. but if your aim is | to encourage people to transition from exporting concrete data types to | exporting abstract types only, the latter approach seems more consistent | to me. Again, I didn't follow | 5 possible extension 1 smells of superfluous complexity. There is almost no gain | compared to using tuples, but there's a lot to pay in added types and rules. You may well be right. | 6 possible extension 2 seems a non-starter if we want compositional abstract | patterns, and I certainly do want them. Imagine the example in (4) with | explicit Maybe. | | Being able to have compositional abstract patterns would be the make-or-break | criterion for me. Without them, new syntactic sugar wouldn't be justified, with | them, their precise form is a matter of convenience. I think I must be missing what you mean by a "compositional abstract pattern". Simon

I don't think view patterns are non-linear at all! They are just as linear as Haskell's existing patterns. Definitely no implicit use of equality, for example.
interesting point. the left-hand sides are non-linear, in that variables may appear several times, but the context distinguishes between pattern-variables and expression variables in view patterns, and the parts concerned with matching are linear, so every pattern-variable will still only have a single point of definition. perhaps that is sufficient to avoid confusion. but the idea that bindings have a left to right bias is new to Haskell patterns, and switching formal and actual parameters can now be statically different, not just dynamically different. Unless the plan is to treat the following two as equivalent? let { f1 p (p -> ()) = () } in f1 return () let { f2 (p -> ()) p = () } in f2 () return
I've added a section called "Nesting".
it certainly makes the point. the part I didn't get at once was that I can build up abstract patterns from view patterns as I would build up abstract data from abstract constructors, and still be able to bind sub-structures to variables.
| 3 what you call first class abstractions are not entirely orthogonal to view patterns. | taking Tullsen's and my own proposal as examples: I'm afraid I don't follow this. I think they are entirely orthogonal.
true first-class patterns, in whatever form, include the functionality provided by view patterns as a subset. only the syntax differs, and the means of variable binding. since we are aiming for a smooth integration with the rest of current Haskell, these differences are important, but they don't make the approaches orthogonal. Tullsen has the pattern binder construct (Section 4.1), which includes the ability to apply any pattern function (functions of type a->Maybe b) anywhere inside a pattern using the % construct. The result is matched against a pattern, which can be a variable. which covers the two aspects of view patterns. and as I've shown for the lambda-match library, one can compose pattern functions in the same way as one builds up a pattern from constructors, ie every part of the pattern is a pattern function. since I don't have syntactic sugar for variable binding, that second aspect of view patterns is a little more awkward. but it can be done in at least two ways, using the logic variable emulation I showed, or something similar to the result of Tullsen's translation of pattern binders. again covering both aspects of view patterns, without additional extensions.
| 4 whether to use view patterns inside ordinary patterns, or whether to build up | patterns from abstract de-constructors (just as expressions are built from | abstract constructors) may seem only a question of style. but if your aim is | to encourage people to transition from exporting concrete data types to | exporting abstract types only, the latter approach seems more consistent | to me. Again, I didn't follow
I wasn't very clear, as I was still trying to get a handle on what view patterns can do. Sorry about that. Perhaps my second mail has already clarified my misconception, but let me try again: concrete data structures are built from concrete data constructors. concrete patterns are built from concrete data constructors (which thereby double as data de-constructors). abstract data structures are built from abstract data constructors, hiding the concrete representation. abstract patterns are built from abstract data-deconstructors (in our current context, that means pattern functions of type a -> Maybe b, for some a,b). my concern was whether it makes sense to use view patterns as abstract de-constructors inside otherwise concrete patterns, or whether one should encourage a wholesale switch to abstract patterns. as long as I can do the latter, I don't mind if the former is also possible.
I think I must be missing what you mean by a "compositional abstract pattern".
most of the examples suggested that view patterns are used one a case by case basis, to select components from an adt part of a parameter. the alternative I'm aiming for, as exhibited in the consP example, would be to build patterns systematically from view patterns used as abstract de-constructors, composed in the same way as one would compose the abstract constructors to build the abstract data structure. in other words, you define your pattern constructors once, with the adt, and export them; and anytime you want to match somethind of that abstract type, you simply compose your pattern from those abstract pattern constructors. is that clearer? Claus

On Wed, 24 Jan 2007, Claus Reinke wrote:
the alternative I'm aiming for, as exhibited in the consP example, would be to build patterns systematically from view patterns used as abstract de-constructors, composed in the same way as one would compose the abstract constructors to build the abstract data structure. in other words, you define your pattern constructors once, with the adt, and export them; and anytime you want to match somethind of that abstract type, you simply compose your pattern from those abstract pattern constructors.
This would cause an awful lot of kludging to get around the fact you need to declare a new ADT to declare new abstract deconstructors, and requires an additional extension for abstract deconstructors to be typeclass methods - something abstract constructors can do for free. Neither seems gainful to me. -- flippa@flippac.org Performance anxiety leads to premature optimisation

the alternative I'm aiming for, as exhibited in the consP example, would be to build patterns systematically from view patterns used as abstract de-constructors, composed in the same way as one would compose the abstract constructors to build the abstract data structure.
This would cause an awful lot of kludging to get around the fact you need to declare a new ADT to declare new abstract deconstructors, and requires an additional extension for abstract deconstructors to be typeclass methods - something abstract constructors can do for free. Neither seems gainful to me.
I don't understand? you can define deconstructors for concrete types as well, as many as you like; it is just that when the representation is not hidden in an ADT, noone hinders me from bypassing your deconstructors and go for the concrete representation instead of the abstract representation. and how did additional extensions or typeclasses get into the picture?? perhaps a concrete example will help. as I used the lists-as-arrays example for lambda-match, here it is again for view patterns (implementation not repeated, List made abstract, untested..): module ListArray(List(),nilA,nullA , nilAP ,consA,headA,tailA , consAP ,snocA,initA,tailA , snocAP ) where ..imports.. -- our own array list variant data List a = List (Array Int a) -- constructors, tests, selectors; cons and snoc view nilA :: List a nullA :: List a -> Bool consA :: a -> List a -> List a headA :: List a -> a tailA :: List a -> List a snocA :: List a -> a -> List a lastA :: List a -> a initA :: List a -> List a -- we also define our own pattern constructors nilAP = guard . nullA consAP l = do { guard $ not (nullA l); return ( headA l, tailA l ) } snocAP l = do { guard $ not (nullA l); return ( initA l, lastA l ) } module Examples where import ListArray anA = consA 1 $ consA 2 $ consA 3 $ consA 4 nilA mapA f (nilAP -> ()) = nilA mapA f (consAP -> (h,t)) = consA (f h) (mapA f t) foldA f n (nilAP -> ()) = n foldA f n (consAP -> (h,t)) = f h (foldA f n t) foldA' f n (nilAP -> ()) = n foldA' f n (snocAP -> (i,l)) = f (foldA' f n i) l palindrome (nilAP -> ()) = True palindrome (consAP -> (_, nilAP -> () ) = True palindrome (consAP -> (h, snocAP -> (m,l))) = (h==l) && palindrome m no need for typeclasses so far. we use abstract data and pattern constructors for adts, just as we use concrete data and pattern constructors for concrete types. we choose what view to take of our data simply by choosing what pattern constructors we use (no need for type-based overloaded in/out). and since our pattern constructors are simply functions, we get pattern synonyms as well. we could, I guess, try to package data and pattern constructors together, either by typeclasses: class Cons t where cons :: t instance Cons (a->List a->List a) where cons = ListArray.cons instance Cons (List a->(a,List a)) where cons = ListArray.consP or by declaring consP as the deconstructor corresponding to the cons constructor, as Mark suggested: cons :: a -> List a -> List a cons# :: List a -> (a,List a) both versions could then be used to select the pattern or data constructor, depending on whether cons was used in a pattern or expression context. but neither of these seems strictly necessary to get the benefit of views. if view patterns turn out to be practical, one could then go on to redefine the meaning of data type declarations as implicitly introducing both data and pattern constructors, so f (C x (C y N) = C y (C x N) might one day stand for f (cP -> (x, cP -> (y, nP))) = c y (c x n) but it seems a bit early to discuss such far-reaching changes when we haven't got any experience with view patterns yet. in the mean-time, one might want to extend the refactoring from concrete to abstract types (HaRe has such a refactoring), so that it uses view patterns instead of eliminating pattern matching. since others have raised similar concerns about needing type-classes, I seem to be missing something. could someone please explain what? Claus

Claus Reinke wrote:
mapA f (nilAP -> ()) = nilA mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)
foldA f n (nilAP -> ()) = n foldA f n (consAP -> (h,t)) = f h (foldA f n t)
To me this exactly illustrates why view patterns are a bad idea: you've taken some concrete type, abstracted it to replace the actual structure by a list structure, then defined map and fold over the list structure. This means that map and fold can't take advantage of the actual concrete structure and are therefore condemned to use the inefficient linear structure imposed by the list abstraction. For example implementing map over a tree directly, gives the possibility of parallel execution since different subtrees can be mapped independently. But when you view the tree abstractly as a list, no such parallel execution can take place. Therefore surely it is better that map and fold are defined for each ADT separately, with the separate definitions hidden behind a type class, than to attempt to define them "outside" the definition of the ADT using view patterns? Brian. -- http://www.metamilk.com

mapA f (nilAP -> ()) = nilA mapA f (consAP -> (h,t)) = consA (f h) (mapA f t)
foldA f n (nilAP -> ()) = n foldA f n (consAP -> (h,t)) = f h (foldA f n t)
yes, maps and folds are likely to be parts of the ADT interface, rather than defined on top of it. I just used them as simple and familiar examples, so that we have something to compare them with.
To me this exactly illustrates why view patterns are a bad idea:
whether or not an ADT interface is well designed, according to some metric, does not tell us whether or not the language features used in the code are good or not. hiding the internal representation always raises questions of whether the exposed interface is still expressive enough or allows efficient code to be written, even without view patterns. in other words, ADTs do not only conflict with the ease of pattern matching, but also with other possible advantages of using the internal representation directly. view patterns help to address the convenience/readability issue, but the other issues remain to be addressed by careful interface design. in this particular case, I believe that separate compilation is the main concern standing in the way of optimizing the abstract view away. Claus
you've taken some concrete type, abstracted it to replace the actual structure by a list structure, then defined map and fold over the list structure. This means that map and fold can't take advantage of the actual concrete structure and are therefore condemned to use the inefficient linear structure imposed by the list abstraction.
For example implementing map over a tree directly, gives the possibility of parallel execution since different subtrees can be mapped independently. But when you view the tree abstractly as a list, no such parallel execution can take place. Therefore surely it is better that map and fold are defined for each ADT separately, with the separate definitions hidden behind a type class, than to attempt to define them "outside" the definition of the ADT using view patterns?
Brian. -- http://www.metamilk.com

| is that clearer? yes, thanks. I'm not quite sure whether it all means you think view patterns are good; or that they would be good with a tweak; or that something else would be better. Do feel free to edit the wiki to articulate any design alternatives that you think deserve consideration. Regardless of whether any of this gets implemented, I think the wiki page can usefully summarise a description of at least a local part of the design space. Simon

I'm not quite sure whether it all means you think view patterns are good; or that they would be good with a tweak; or that something else would be better.
probably because my opinion has been changing;-) at first, I wasn't convinced, now I think it depends on the details. as Mark said, such syntactic extensions of conventional patterns are not strictly necessary since we know how to avoid them completely (using data parsing). so for a new functional language, I too would like to drop patterns as built-ins, providing their functionality via sugar and libraries. but as far as Haskell is concerned, I am perhaps less radical in my approach than Mark is: Haskellers have invested an awful lot of work in those conventional patterns, in readibility, in optimisations, and in linking them with other extensions (eg., type system extensions). that is why I proposed the lambda-match construct to complement the library Control.Monad.Match, so that conventional patterns could be used within the data parsing framework. and that is why I think view patterns are useful: they allow us to embed data parsing into conventional patterns, reusing existing syntax for binding pattern variables while still allowing us to define our own pattern constructors. so I'd like to have both lambda-match and view patterns, supported by Control.Monad.Match, and well integrated. but if suggestions to make Maybe explicit in view patterns, or to drop it alltogether, carry the day, I might lose interest. also, I'd like the syntax to stay close to conventional constructors, rather than close to pattern guards. regarding first-class abstractions/terminology: for myself, I have settled on using "first-class matches" (or "first-class match alternatives") for the likes of the lambda-match construct (left-hand side pattern, right-hand side expression), and "first-class patterns" for proposals that actually allow to abstract over the left-hand sides of matches. both first-class matches and first-class patterns tend to use the common framework of MonadPlus instances for match failure and fall-through, as a generalisation of the good old monadic combinator parsers on strings. for this framework I use the term "monadic data parsing". regarding syntax for view patterns: I like the prefix form, but agree that the use of "->" is unfortunate. If it wasn't for pattern constants, I'd probably just use application (lower case identifiers in function position in a pattern can only be views, unless someone suggests other uses for that syntax; and the last parameter of a view has to be a pattern). The next best thing, to emphasize that we're essentially computing patterns, would be to borrow TH's notation for splicing, using $(view p1..pn) pattern instead of view p1..pn -> pattern Claus

On Jan 25, 2007, at 3:49 AM, Claus Reinke wrote:
but as far as Haskell is concerned, I am perhaps less radical in my approach than Mark is: Haskellers have invested an awful lot of work in those conventional patterns, in readibility, in optimisations, and in linking them with other extensions (eg., type system extensions).
I actually would agree. The purist in me would want to use a language with a simple exhaustive case construct and pattern-binders and no more; but the pragmatist in me does, usually, go with the flow of the language and use some of the more complex pattern-matching constructs. However, I did edit the web page to include an improved description of First Class Patterns, for a point of reference and comparison. - Mark
participants (5)
-
Brian Hulley
-
Claus Reinke
-
Mark Tullsen
-
Philippa Cowderoy
-
Simon Peyton-Jones