
Hi folks Having spent the last week hacking, I've found a common irritation, so I have a proposal to mitigate it. Of course, this issue may not bug anyone else, so I'm a little hesitant. In pessimal pedagogical order, the proposal: pattern synonyms. I want to be allowed to write stuff like P x y z = C x (y, [z]) defining a capitalised symbol with parameters used linearly in a pattern on the right-hand side. Pattern synonyms should be fully applied and expand macro-style wherever patterns or terms appear, hence should not give rise to cycles, just like type synonyms. It seems (and is) trivial. Why would it help? Well, it would help me, because I often write more complex types than strictly necessary to represent data in order to expose its structure and thus gain free equipment. For example, taking newtype Comp f g x = Comp (f (g x)) -- applicative if f and g are newtype Prod f g x = Prod (f x, g x) -- applicative if f and g are newtype Const x y = Const y -- applicative if x is a monoid newtype Id x = Id x -- trivially applicative newtype Any = Any Bool -- equipped with the disjunctive monoid structure all of which I keep lying around anyway, I might well write type MyEffect = Comp Maybe (Prod (Const Any) Id) which is the same as type MyEffect' x = Maybe (Bool, x) except that (1) MyEffect :: * -> * is an applicative functor without further ado (because it is composed from suitable components), hence I get lots of free kit for traversing data with it. (If you're interested, we use this to update terms where some variables have been changed and others have been deleted entirely: we want to know the new term if it exists, and whether it differs from the old one.) MyEffect' is meaningless. (2) Pattern matching on MyEffect x is much more annoying than on MyEffect' x. I want to write Bang :: MyEffect x Bang = Comp Nothing Bing :: x -> MyEffect x Bing x = Comp (Just (Prod (Any True), Id x)) Dull :: x -> MyEffect x Dull x = Comp (Just (Prod (Any False), Id x)) and have done with it. Does this happen to anyone else? Would pattern synonyms help? Thought I'd ask, anyway. All the best Conor

Conor McBride
P x y z = C x (y, [z])
Isn't this idea very similar to views, and pattern-guards? For instance, you could rewrite your example thus: data EffectView x = Bang | Bing x | Dull x view :: MyEffect x -> EffectView x view (Comp Nothing) = Bang view (Comp (Just (Prod (Any True), Id x))) = Bing x view (Comp (Just (Prod (Any False), Id x))) = Dull x my_function e | Bang <- view effect = ... | Bing x <- view effect = ... x ... | Dull x <- view effect = ... x ... Regards, Malcolm

Malcolm Wallace wrote:
Conor McBride
writes: P x y z = C x (y, [z])
Isn't this idea very similar to views, and pattern-guards?
Clearly related, but rather cheaper. I don't want to make remarks, positive or negative about either of those proposals at this juncture. I see pattern synonyms, like type synonyms, as a convenient abbreviation mechanism in a part of the language where verbosity is currently compulsory.
For instance, you could rewrite your example thus:
data EffectView x = Bang | Bing x | Dull x
view :: MyEffect x -> EffectView x view (Comp Nothing) = Bang view (Comp (Just (Prod (Any True), Id x))) = Bing x view (Comp (Just (Prod (Any False), Id x))) = Dull x
my_function e | Bang <- view effect = ... | Bing x <- view effect = ... x ... | Dull x <- view effect = ... x ...
You forgot to define the term behaviour also. Pattern synonyms may be used to construct as well as to match values. Of course, I could also write weiv :: EffectView x -> MyEffect x weiv Bang = ... weiv (Bing x) = ... weiv (Dull x) = ... or I could just add them as definitions with lower-case initials. The pattern synonym gives me both at once, and their relationship. Moreover, I don't have to either (a) cover the entire type with pattern synonyms or (b) write a partial view; I just abbreviate whenever I find it convenient. More moreover, your way, the need to interpolate the view encoder forces me to do my matching in a guard, rather than an argument pattern, hence the need to say 'view effect' three times, or however many it happens to be, and some irritation in mixing matching on MyEffect x with matching on other arguments. But perhaps constructing explicit embedding-projection pairs is a better solution than an abbreviation mechanism, for most people's needs. All the best Conor This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

Dear all, Conor wrote:
You forgot to define the term behaviour also. Pattern synonyms may be used to construct as well as to match values.
Conor and I discussed this over lunch. Specifically, we talked about whether the right hand side of a pattern synonym would be any Haskell pattern (including "_", "~", possibly "!"), or restricted to the intersection between the patterns and terms, as Conor propose that pattern synonyms also be used for construction. By adopting some simple conventions, like replacing "_" by "undefined" when a synonym is used as a term for construction, it is clear that one can be a bit more liberal than a strict intersection between the pattern and current expression syntax. Incidentally, this would be consistent with the way record patterns and record construction currently works. E.g. data Foo = MkFoo {l1 :: T1, l2 :: T2} A pattern "MkFoo {}" expands to "MkFoo _ _", a term "MkFoo {}" expands to "MkFoo undefined undefined". Moreover, didn't someone (John Mecham?) propose that "_" be a valid term anyway, standing for "undefined" (with an explicit requirement of keeping track of the source code position)? Maybe "~" (and "!") wouldn't cause much trouble either. I like the idea, but it would be nice if the RHS of a pattern synonym definition really coudl be any Haskell pattern, without any additional restriction (except that it has to be acyclic). All the best, /Henrik -- Henrik Nilsson School of Computer Science and Information Technology The University of Nottingham nhn@cs.nott.ac.uk This message has been checked for viruses but the contents of an attachment may still contain software viruses, which could damage your computer system: you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation.

On 2/16/06, Henrik Nilsson
Conor and I discussed this over lunch.
Specifically, we talked about whether the right hand side of a pattern synonym would be any Haskell pattern (including "_", "~", possibly "!"), or restricted to the intersection between the patterns and terms, as Conor propose that pattern synonyms also be used for construction.
By adopting some simple conventions, like replacing "_" by "undefined" when a synonym is used as a term for construction, it is clear that one can be a bit more liberal than a strict intersection between the pattern and current expression syntax.
I would speak against this. I like the idea of pattern synonyms, but I think they should be just that - pattern synonyms, and not try to mix in expressions as well. With the current (H98) pattern situation, it *might* be possible to tweak things so that all patterns have an expressional meaning (e.g. "_" as "undefined"), but 1) it would be fairly construed in many cases, and 2) it would complicate making extensions to the pattern matching facility. (Shameless plug:) In particular I'm thinking about our extension HaRP [1] that adds regular expressions to pattern matching over lists. The ability to define pattern synonyms would be really useful in conjunction with HaRP, but if those patterns are required to also have an expressional meaning it would make things fairly complicated, not to say impossible. Instead I would like to propose an extension to the proposed extension in another direction: Adding in (pattern) guards. Consider patterns like IsSpace x = x | isSpace x Last x = xs | x <- last xs This would in particular go well together with HaRP, where you in some cases need guards to be inlined, e.g. words [ (IsSpace _)*!, (/ xs@:(_*), (IsSpace _)*! /)* ] = xs Btw, why not consider adding regular patterns a la HaRP to Haskell'? :-) (Disclaimer: I'm not really serious, like Lennart I don't really feel that any of this has any place in Haskell'. But as for the future beyond that, I am serious.) [1] http://www.cs.chalmers.se/~d00nibro/harp

Most of this discussion on patterns (except for views) seems too much focused on concrete data types. (regexps for lists: what a horrible thought :-) This is just the thing to avoid in software design. (Don't expose implementation details, use interfaces etc.) On the other hand, this is exactly what keeps the refactoring people and their tools happy: they will never run out of work as long as the above advice isn't followed ... -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Most of this discussion on patterns (except for views) seems too much focused on concrete data types. (regexps for lists: what a horrible thought :-) This is just the thing to avoid in software design. (Don't expose implementation details, use interfaces etc.)
There's nothing in HaRP that would not work seamlessly with any sequential datatype through an interface of destructors, and clearly that's the Right (TM) way to go. The current implementation is just proof of concept. :-) IMO your comment only further speaks for my proposal to add guards to pattern synonyms. With an interface of destructors, you could define patterns that don't say anything about the underlying implementation, e.g. Head x = xs | x <- head xs where the head function comes from some interface for sequences. This is not something that can be done currently, nor with the initial proposal for pattern synonyms. /Niklas

Conor McBride wrote:
Hi folks
Having spent the last week hacking, I've found a common irritation, so I have a proposal to mitigate it. Of course, this issue may not bug anyone else, so I'm a little hesitant. In pessimal pedagogical order, the proposal: pattern synonyms.
Yes, I quite often wish I had them. But keeping in line with the original Haskell' charter I've refrained from proposing them since they are unimplemented. -- Lennart
participants (7)
-
Conor McBride
-
Conor McBride
-
Henrik Nilsson
-
Johannes Waldmann
-
Lennart Augustsson
-
Malcolm Wallace
-
Niklas Broberg