
I agree that if (n+k) patterns go, then so should k patterns. Both are overloaded, and that's the root of their complexity. Personally I think ~ patterns are great, and we are now talking about ! patterns, a kind of dual to ~ patterns. So at least I think we should un-couple the two discussions. Simon | -----Original Message----- | From: haskell-prime-bounces@haskell.org [mailto:haskell-prime-bounces@haskell.org] On Behalf Of | Olaf Chitil | Sent: 26 January 2006 17:01 | To: haskell-prime@haskell.org | Subject: Removal candidates in patterns | | | I am very please to see on the Wiki also a list of removal candidates | and that these include n+k patterns and ~ patterns. | | I'd like to add one pattern to this list of removal candiates: k | patterns, that is, numeric literals. | | Why do I want to get rid of these three patterns? Because all three | caused me no end of trouble when implementing the program transformation | of the Haskell tracer Hat. Hat actually still doesn't handle nested ~ | patterns. | | Why are these patterns so hard to implement for Hat? Surely the Haskell | report gives a translation into simple core Haskell. Well, Hat does not | use this translation because it does not want to be an inefficient | pattern matcher (leave that job to the compiler) but produce a trace of | the Haskell program as it is written. However, both n+k and k patterns | cause calls of functions ( (-), (==) etc) that Hat has to record in its | trace. Also ~ patterns do not fit the simple rewriting semantics of the | Hat trace and hence have to be recorded specially. While in simple cases | that occur in practice it is pretty straightforward to remove n+k, k and | ~ patterns from a larger pattern while keeping the rest of the larger | pattern intact, in the general case this is incredibly hard. | | Iff n+k patterns are removed, there is little good use for k patterns | either. Since the introduction of monadic IO the ~ pattern is hardly | used in practice either. In all the simple cases that these three are | currently used in practice, it is easy for the programmer to define | their function in an alternative way. | | So get rid of these three and pattern matching becomes so much more simple. | | Ciao, | Olaf | _______________________________________________ | Haskell-prime mailing list | Haskell-prime@haskell.org | http://haskell.org/mailman/listinfo/haskell-prime

On Thu, 2006-01-26 at 17:31 +0000, Simon Peyton-Jones wrote:
I agree that if (n+k) patterns go, then so should k patterns. Both are overloaded, and that's the root of their complexity.
I have to say that we use 'k' patterns in teaching all the time, though we do not teach n+k patterns. There are lots of cases where it's convenient to say: foo 0 = ... foo n = ... Intuitively it seems reasonable to me that 1 is a constructor for the Int type just as 'c' is a constructor for type Char, and since it's a constructor we can pattern patch on it. To be honest, the difficulty of the internal translation needed for tools seems less important to me than the convenience for users. I don't think the difference that character constants are not overloaded where as numeric constants are overloaded causes any difficult in understanding for users. Duncan

As response to both Aaron and Duncan,
foo 0 = ... foo n = ...
And what about the negative numbers? For negative numbers the second equation matches, which in 90% of all cases in practise has never been written for them. Aaron's Ackerman function disappears in infinite recursion... Besides, what is ack 0.5 0.5? The use of n+k patterns, but also the definition pattern above wrongly lead programmers to believe that they are dealing with natural numbers. There is no nice primitive recursion for integers. Even worse, without a type signature restricting its type, foo will be defined for all numeric types. For Float or Rational it makes hardly any sense. If Haskell had a type for natural numbers I'd be in favour of n+k and k patterns (working only for this type, not any other numerical type). Using primitive recursion on integers or even arbitrary numbers is misleading. You can teach primitive recursion nicely for algebraic data types, because the recursive pattern of the function definition follows the recursive pattern of the type definition. With respect to tools of which Hat is one example: If it is hard to build tools, then less tools will be built. Compare the number of tools for Scheme with those for Haskell. Most tools grow out of student projects or research projects; these have rather limited resources. Ciao, Olaf

On Thu, 2006-01-26 at 19:35 +0000, Olaf Chitil wrote:
As response to both Aaron and Duncan,
foo 0 = ... foo n = ...
And what about the negative numbers? For negative numbers the second equation matches, which in 90% of all cases in practise has never been written for them. Aaron's Ackerman function disappears in infinite recursion... Besides, what is ack 0.5 0.5?
Isn't the same true for: foo n | n == 0 = ... | otherwise = ... It's still going to fail for negative numbers.
The use of n+k patterns, but also the definition pattern above wrongly lead programmers to believe that they are dealing with natural numbers. There is no nice primitive recursion for integers. Even worse, without a type signature restricting its type, foo will be defined for all numeric types. For Float or Rational it makes hardly any sense.
The above example is still defined for all numeric types. Eliminating that syntax form doesn't remove those problems.
If Haskell had a type for natural numbers I'd be in favour of n+k and k patterns (working only for this type, not any other numerical type).
I'm in favour of removing n+k patterns too.
Using primitive recursion on integers or even arbitrary numbers is misleading. You can teach primitive recursion nicely for algebraic data types, because the recursive pattern of the function definition follows the recursive pattern of the type definition.
Char is a type that is not constructed recursively and yet no one seems to have problems with character literals as constructors and thus as patterns. Each character literal is a Char constructor. Why can't each numeric literal be a constructor for the numeric types? I think it's a perfectly reasonable mental model for people to believe that: data Char = 'a' | 'b' | 'c' | ... data Int = ... -2 | -1 | 0 | 1 | 2 | ... I don't see why we should remove one and not the other. Students will ask why the can pattern match on strings, characters and booleans but not numbers. Perhaps primitive recursion on integers is misleading, but people will still write foo n | n == 0 = ... | otherwise = ... where they previously wrote foo 0 = ... foo n = ... so what have we gained except less notational convenience? Not all pattern matching on numeric literals is involved with recursion on integers, where as virtually all n+k patterns is used for that purpose. So there is some distinction between the two forms. n+k patterns are a quirk of the numeric types. k patterns are regular with other types in the language.
With respect to tools of which Hat is one example: If it is hard to build tools, then less tools will be built. Compare the number of tools for Scheme with those for Haskell. Most tools grow out of student projects or research projects; these have rather limited resources.
It's partly the complexity of the language and partly because our latest language spec (H98) is not the language that we all use (H98 + various extensions). I'm sure Haskell-prime will help in this area. I don't mean to belittle the difficulty of building tools. I know how hard it is, I'm trying to build one too. Duncan

Duncan Coutts wrote:
I think it's a perfectly reasonable mental model for people to believe that: data Char = 'a' | 'b' | 'c' | ... data Int = ... -2 | -1 | 0 | 1 | 2 | ...
I don't see why we should remove one and not the other. Students will ask why the can pattern match on strings, characters and booleans but not numbers.
Numbers are special because they are overloaded. A numeric literal is an element of many types. That clearly distinguishes them from other literals.
Perhaps primitive recursion on integers is misleading, but people will still write
foo n | n == 0 = ... | otherwise = ...
where they previously wrote
foo 0 = ... foo n = ...
so what have we gained except less notational convenience?
Discourage anyone from teaching primitive recursion on integers. Recursion on integers then has to be taught as a separate topic, giving opportunity to point out the pitfalls. Sure, it doesn't prevent anyone from writing anything.
Not all pattern matching on numeric literals is involved with recursion on integers, where as virtually all n+k patterns is used for that purpose.
I think there are very few situations where you would use k patterns without recursion.
So there is some distinction between the two forms. n+k patterns are a quirk of the numeric types. k patterns are regular with other types in the language.
As I said above, they are not regular because of overloading.
It's partly the complexity of the language and partly because our latest language spec (H98) is not the language that we all use (H98 + various extensions). I'm sure Haskell-prime will help in this area.
I hope as well that Haskell' will be the language that most people will use and some extensions are certainly required for practical use. I just want to get rid of superfluous features. Ciao, Olaf

On Thu, Jan 26, 2006 at 07:35:42PM +0000, Olaf Chitil wrote:
As response to both Aaron and Duncan,
foo 0 = ... foo n = ...
And what about the negative numbers?
(I agree with Duncan re this).
If Haskell had a type for natural numbers I'd be in favour of n+k and k patterns (working only for this type, not any other numerical type).
Haskell (FSVO "Haskell") has several types for natural numbers: Word8, Word16, Word32, Word64. I'd also like to see a Natural type (analogous to Integer) (you might also argue for Word, analogous to Int), and I'd like to use k patterns with all of them. A Natural class would also make some sense. Then we could have, e.g., (^) :: (Num a, Natural b) => a -> b -> a although that does cause problems with Haskell's libraries being strongly biased towards Int (and changing that probably breaks an awful lot of code). However, it would seem odd to me, as a new user, that I could say foo 1 = 0 foo n = n but not foo (-1) = 0 foo n = n On n+k patterns, I think they make code a lot more concise and easier to read, as well as allowing code to match specifications much more closely. In fact, every reason why in a mathematical definition you would say f (x+1) = g x rather than f x | x >= 1 = g x' where x' = x - 1 applies equally to code IMO. I think there is something to be said for making n+k patterns have a Natural type rather than an Integral type, though, as we are requiring that n be at least 0. k patterns are less clear cut due to Rational, but on balance I'd be happy with k patterns being Integral only as people writing f 1.1 = 0 probably normally don't really mean that. So in conclusion, I'm in favour of keeping both n+k and k patterns, and restricting n+k patterns to Natural types and k patterns to Integral types.
With respect to tools of which Hat is one example: If it is hard to build tools, then less tools will be built. Compare the number of tools for Scheme with those for Haskell. Most tools grow out of student projects or research projects; these have rather limited resources.
I don't think this makes it significantly harder to make tools, there is a simple source transformation to eliminate these constructs (your reasons for disliking using it I didn't fully understand). If tools like hat think of these constructs as, and shows them to the user as, their expanded versions then we would be no worse off than if they weren't in the language. Thanks Ian

On Thu, 26 Jan 2006, Ian Lynagh wrote:
A Natural class would also make some sense. Then we could have, e.g., (^) :: (Num a, Natural b) => a -> b -> a although that does cause problems with Haskell's libraries being strongly biased towards Int (and changing that probably breaks an awful lot of code).
You could make "instance Natural Int" (etc) available in some module that legacy programs could import.
So in conclusion, I'm in favour of keeping both n+k and k patterns, and restricting n+k patterns to Natural types and k patterns to Integral types.
I like this idea. Cheers, Ganesh

On Thu, Jan 26, 2006 at 11:03:01PM +0000, Ian Lynagh wrote:
On Thu, Jan 26, 2006 at 07:35:42PM +0000, Olaf Chitil wrote:
If Haskell had a type for natural numbers I'd be in favour of n+k and k patterns (working only for this type, not any other numerical type).
Haskell (FSVO "Haskell") has several types for natural numbers: Word8, Word16, Word32, Word64. I'd also like to see a Natural type (analogous to Integer) (you might also argue for Word, analogous to Int), and I'd like to use k patterns with all of them.
I think Olaf meant an inductively defined type for natural numbers. What's nice about that idea is that many canonical and teaching examples, such as "ack" given in this thread, still work--and now provide an honest introduction to structural recursion. Andrew

On Thu, Jan 26, 2006 at 07:35:42PM +0000, Olaf Chitil wrote:
If Haskell had a type for natural numbers I'd be in favour of n+k and k patterns (working only for this type, not any other numerical type).
Ideally, I'd like to see pattern matching on numbers be seperated into its own class independently of 'Num' so we can decide whether to allow pattern matching independently of whether something is a 'Num' something like class NumMatchable a where numMatches :: Integer -> a -> Bool -- John Meacham - ⑆repetae.net⑆john⑈

Simon Peyton-Jones wrote:
I agree that if (n+k) patterns go, then so should k patterns. Both are overloaded, and that's the root of their complexity.
Personally I think ~ patterns are great, and we are now talking about ! patterns, a kind of dual to ~ patterns. So at least I think we should un-couple the two discussions.
I agree that it is sensible to decouple the two discussions, so just add k patterns to n+k patterns. However, ~ patterns are really currently the most complicated patterns and ! patterns match them in their complexity. Personally I believe that programmers should strive for more laziness, rarely for more strictness. I do not like that you can add ! in lots of places where it doesn't make any difference, e.g. f [] !x = rhs1 f (y:ys) !x = rhs2 is the same as f [] !x = rhs1 f (y:ys) x = rhs2 Your motivating example f2 !x !y | g x = rhs1 | otherwise = rhs2 I would express as f2 x y = x `seq` y `seq` if g x then rhs1 else rhs2 Now you will probably counter with a definition where you can fall through the guard to the next equation. In my opinion that just shows how horrible guards are (and I would propose their removal if I saw any chance of success). Ciao, Olaf

On 26/01/06, Simon Peyton-Jones
I agree that if (n+k) patterns go, then so should k patterns. Both are overloaded, and that's the root of their complexity.
I'm not so sure about that. I don't use (n+k) patterns at all, but I do get fairly regular use out of k patterns. (n+k) patterns can seem like an odd special case in everything but Nat, but k patterns are often the nicest way to handle base cases, and save you from writing awkward-looking guards. Sure, they're not usually appropriate for floating point computations, but for integral and rational types, they work very well. (even if you can't pattern match against fractions) One possibility is that k patterns could be generalised to arbitrary members of Eq, rather than just being used for numbers. We could even make variables bound in the parameter list available. So for a simplistic example, one could write: f :: (Eq a, Num a) => a -> a -> a f x x = x -- if the two parameters match, give their common value f _ _ = 0 -- otherwise give 0. The first 'x' would pattern match as usual, and the second would compare for equality with the first. We'd have to work out the exact syntax for them -- essentially, it would just involve detecting an arbitrary expression which was not a pattern. There's some context sensitivity there with the option of referring to previously bound variables though. I'm not sure how often this would be used, and perhaps it's more trouble than it's worth, but at least it leaves no further room for generalisation, which makes the feature seem somewhat natural. Even without previous-variable-binding, it subsumes all pattern matching on literals, so it would take some thought to determine if it really makes things more complicated or not.
Personally I think ~ patterns are great, and we are now talking about ! patterns, a kind of dual to ~ patterns. So at least I think we should un-couple the two discussions.
I think so too. Removing ~ patterns seems like a fairly poor idea to me. Sure, they're not very much explicitly used (though everyone uses them implicitly in pattern bindings), but when you want them, they can be fairly important. I think perhaps we just need better coverage of ~ in the tutorials. Now that I think about it, I rather like the idea of ! patterns as well. They make ~ patterns seem more natural by contrast. Strictness can on occasion be just as important as laziness, and this notation makes it more convenient to obtain in simple cases. How to get a similarly pretty notation for more structured strictness annotations is a bit of a concern. I wonder whether some of the Control.Parallel.Strategies library should be more strategically located? :) - Cale

The arguments of Ian Lynagh, Ganesh Sittampalam, Claus Reinke and Cale Gibbard about restricting k patterns to class Integral, introducing a class Natural and the role of class Eq prove my point that k patterns are special, different from data constructors or character literals. They are special, far more complex than most people think, and very easy to avoid. I do understand that probably everybody learning functional programming learned k patterns very early on (in other languages such as Miranda there is no overloading problem) and hence find it hard to make the small change of using explicit equality instead. (And yes, removing k-patterns will break a lot of Haskell programs.) Higher-order functions substantially increase the expressivity of the programming language. k-patterns are just an odd decorative element. I was probably wrong to start my argument with talking about Hat. This is just what made me personally look into k, n+k and ~ patterns. The general argument is just that every language feature has its costs (for tools, for research, for teaching,...) and hence any language feature should be truely useful, not just convenient (naturally the distinction is not clear cut). Ciao, Olaf
participants (8)
-
Andrew Pimlott
-
Cale Gibbard
-
Duncan Coutts
-
Ganesh Sittampalam
-
Ian Lynagh
-
John Meacham
-
Olaf Chitil
-
Simon Peyton-Jones