
On 26 January 2006 16:07, John Hughes wrote:
Simon Marlow wrote:
I wonder if there's an alternative solution along these lines:
- We use ParialTypeSignatures to make bindings monomorphic:
http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/PartialTyp
eSigs
eg.
x :: _ x = (+1)
- we make it a static error for a variable bound by a simple pattern binding ("x = e") to be overloaded, unless a type signature is given. The error message would explain the problem, and how to fix it. Alternatively, we make it a strong warning.
It seems to me that the partial type signatures extension provides a lot of bang for the buck - it gives us a way out of the MR in addition to partial type signatures.
I don't like this. Once students start dropping type signatures (which they do pretty soon for local variables in where-clauses), they would sometimes-- unpredictably as far as they're concerned--get an error message telling them they must put one back in again, but it's enough to write x :: _. Can you imagine explaining to an average student in the first year why they MUST put in a type signature, but it doesn't need to include a type???
Understood, but what about when the student writes '=' instead of ':=' by mistake - most of the time it'll work! But occasionally they fall foul of the reason we had the MR in the first place. Presumably the compiler should emit a noisy warning, but continue anyway? Won't that be confusing? How about an even simpler solution: *All* pattern and variable bindings are monomorphic unless a type signature is given. I wonder how much code this would break? It can't be too bad, because John is suggesting using := for variable bindings everywhere as a starting point. Also, SML users live with something very similar. How often do we really need polymorphism in a variable or pattern binding? I'm guessing probably not that often, because by far the most common use of polymorphism is in functions. You lose if you write mymap = map or mynil = [] and then try to use those at more than one type, but I'm guessing that's quite rare, and you can still give a type signature. I'd be very interested to tweak this in GHC and see how much code still passes the type checker. Cheers, Simon

Simon Marlow wrote:
How about an even simpler solution:
*All* pattern and variable bindings are monomorphic unless a type signature is given.
I wonder how much code this would break? ... I'd be very interested to tweak this in GHC and see how much code still passes the type checker.
Now that IS an interesting idea. The more I think about it, the more I like it. I suspect very few programs would break, because in many cases such a definition is not only polymorphic but also overloaded, and so already carries a type signature. Actually, I find the need to specify type signatures to get overloading awkward already --but I don't think needing to do so for purely polymorphic variable bindings would be significantly more awkward. I find the right context is often quite hard to predict, and I want to use Hugs or GHCi to compute it rather than figure it out myself. Moreover, I don't like needing to maintain such type signatures when I change code elsewhere. (For example, if I've used association lists as look-up tables, then I'll have Eq constraints on many definitions, and if I then change that to ordered binary trees then I suddenly need to change all those Eqs to Ords. I've known cases where the work needed to do that maintentance was so great that the desirable change to the program could not be made within the time available for the project.) However, this is reasonably a separate problem, which I don't think is made significantly worse by your idea. Perhaps it'll be solved (e.g. by partial type signatures), perhaps not, but in either case I like your suggestion. One more thought. Perhaps we could indicate polymorphism/monomorphism separately from writing a type signature. Suppose, when we want a polymorphic or overloaded variable definition, we were to write poly x = e Likewise, when we want a monomorphic function definition, we could write mono f x y z = e Then we could concisely indicate our intention, while leaving open the possibility of using Hugs or GHCi to compute type signatures, or leaving them out to reduce that part of the maintentance effort. Arguably, writing poly x = e gives a clearer warning that something funny is going on--i.e. there is a risk of repeated computation--than writing a type signature which you then have to examine, to see whether or not it contains a class constraint. But of course, this idea would mean more changes to existing code, adding a poly before variable definitions that currently carry an overloaded type signature. Although since it would be an error to write such a type signature on a definition NOT marked as poly, finding the right places to add it would simply be a matter of recompiling and fixing the errors found. The more I think about it--and recalling that a type signature need not be written anywhere near the definition it refers to--the more I think using type signatures to carry vital information about the *semantics* of a definition is a bad idea. John

John Hughes wrote:
Actually, I find the need to specify type signatures to get overloading awkward already [...] I don't like needing to maintain such type signatures when I change code elsewhere. [...] However, this is reasonably a separate problem, [...]
indeed. I use "constraint collection classes" (without methods) as in: http://141.57.11.163/cgi-bin/cvsweb/lib/Autolib/NFA/Data.hs.drift?rev=1.15 look for class NFAC (it collects the constraints for using type NFA). This allows to write short contexts at the call sites, and make local changes at the definition side. Best regards, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

On Friday 27 January 2006 10:51, Simon Marlow wrote:
How about an even simpler solution:
*All* pattern and variable bindings are monomorphic unless a type signature is given.
My personal opinion is that it should be exactly the other way around: All normal bindings (i.e. using '=') should be as polymorphic and general as possible. An alternative symbol (':=') should be available, but strictly as a means to optimize binding of monomorphic ground values (that are then /guaranteed/ to be computed only once). I think that the language should /never/ force the programmer to consider performance issues from the outset. I see ':=' as something similar to SPECIALIZE or INLINE pragmas -- such things should never be mandatory to get a program to work. Thus, I think, for all programs that are accepted by the compiler, replacing all ':=' by '=' should result in a program that gets accepted as well, it should be semantically equivalent (apart from possibly being slower or consuming more memory). Furthermore, in Haskell there are /thousands/ of other possibilities to ruin the efficiency of your program, most of them a lot less obvious and in fact very hard to optimize away. For instance, compared to all those subtle too-much-laziness performance problems, this one could be easily diagnosed by profiling and also easily fixed by introducing the occasional ':='. Also, the compiler could help by issuing warnings (but only if prompted to do so by some compiler flag). On the other hand, forcing the programmer to write signatures in order to get the most general type of a bound variable -- when this would be avoidable in principle -- is a very bad idea, IMO. Type inference is an extremely valuable feature when prototyping and experimenting. It is also of great help for people who want to explore some of more advanced aspects of Haskell's type system. Asking ghci or hugs to give me the inferred type of a complicated function definition has often given me the decisive insight about how to write a correct version. Just my (hopefully not too uninformed) 2 cents. Ben

On 1/27/06, Benjamin Franksen
All normal bindings (i.e. using '=') should be as polymorphic and general as possible. An alternative symbol (':=') should be available,
I don't want to rain on any parade, but just let me point out that
under the current grammar, := is a constructor.
--
Taral

On Fri, Jan 27, 2006 at 07:04:43PM +0100, Benjamin Franksen wrote:
All normal bindings (i.e. using '=') should be as polymorphic and general as possible.
I agree with the position in the Ben's email. Also, especially since much of the discussion has considered the impact on beginners, I want to recall that the monomorphism restriction can cause highly confusing error messages. They do not necessarily mention "probably cause: monomorphism restriction", and one cannot always find the problem by looking at the error location and the definition. I have a feeling there should be a better example of this issue floating around, but not finding one I'll submit my own: bar :: IO Char bar = foo foo = return 'a' baz = "hello " ++ foo ghc 6.4.1 gives the error try.hs:2:6: Couldn't match `IO' against `[]' Expected type: IO Char Inferred type: [Char] In the definition of `bar': bar = foo If you imagine that baz is buried at the bottom of the module in some test code, you might see how this could be mystifying. After all, there's no list mentioned in foo or bar. (But perhaps the error message could be improved to mention the monomorphism restriction?) My feeling is that when a variable definition should be monomorphic (and thus shared), the programmer ought to give the monomorphic type explicitly, rather than count on some use of the variable (possibly far away in the code) to decide it implicitly. Andrew

One aspect of this discussion I've yet to see that I think is important is, how do the various proposals for removal/modifications of M-R impact implicit parameters? Are implicit parameters likely to be in Haskell'? It seems like the proposal to default to polymorphic binding and have special syntax for monomorphic binding also fixes one of the major probems now with implicit parameters. Rob Dockins

On Fri, Jan 27, 2006 at 06:05:56PM -0500, Robert Dockins wrote:
One aspect of this discussion I've yet to see that I think is important is, how do the various proposals for removal/modifications of M-R impact implicit parameters? Are implicit parameters likely to be in Haskell'? It seems like the proposal to default to polymorphic binding and have special syntax for monomorphic binding also fixes one of the major probems now with implicit parameters.
I strongly doubt it. implicit parameters are quite broken semantically and there are better solutions to the problem they are intended to solve which they never solved that well to begin with. John -- John Meacham - ⑆repetae.net⑆john⑈

Benjamin Franksen wrote:
My personal opinion is that it should be exactly the other way around:
All normal bindings (i.e. using '=') should be as polymorphic and general as possible.
Do you mean *all* bindings, or only top-level ones? If you really mean all, wouldn't e be polymorphic (with type Num a=>a) in, say:
f x = e + e where e = very_expensive_polymorphic_function x
That would be a Very Bad Thing. Twan

On Sat, 28 Jan 2006, Twan van Laarhoven wrote:
Benjamin Franksen wrote:
My personal opinion is that it should be exactly the other way around:
All normal bindings (i.e. using '=') should be as polymorphic and general as possible.
Do you mean *all* bindings, or only top-level ones? If you really mean all, wouldn't e be polymorphic (with type Num a=>a) in, say:
f x = e + e where e = very_expensive_polymorphic_function x
That would be a Very Bad Thing.
Is there any reason in that particular case that the dictionary transform can't produce something like this: f x d = e' + e' where e d = very_expensive_polymorphic_function x d e' = e d ? What's the pathological case that prevents this applying more generally? -- flippa@flippac.org Performance anxiety leads to premature optimisation

On Saturday 28 January 2006 01:13, Twan van Laarhoven wrote:
Benjamin Franksen wrote:
My personal opinion is that it should be exactly the other way around:
All normal bindings (i.e. using '=') should be as polymorphic and general as possible.
Do you mean *all* bindings,
Yes.
or only top-level ones? If you really mean
all, wouldn't e be polymorphic (with type Num a=>a) in, say:
f x = e + e where e = very_expensive_polymorphic_function x
That would be a Very Bad Thing.
Why? The compiler /might/ be able to decide that 'f' is in fact used only monomorphically and thus 'e' can be shared. Even if 'f' is exported (in which case I would most probably write a signature at one time), a compiler that does whole-program analysis can find out. It could even specialize 'f' for each type at which it is used, each specialized version being monomorphic, internally, so that 'e' can be 'maximally shared'. If all else fails, you can always change it to := (or whatever other symbol will be agreed upon) if you want to indicate to the compiler/interpreter: "I'd rather get an error message if I use this polymorphically/overloaded/whatever. This 'e' must be shared at all costs!". Cheers, Ben

Is it really so impossible to implement typeclasses in a way which avoids this problem altogether? Perhaps the need for the MR in the first place is simply an indication that dictionary passing is not a complete solution to implementing typeclasses. It seems quite plausible that there should be an implementation which preserves polymorphism, and yet doesn't result in horrific inefficiency. Do we have a proof (or at least strong evidence) that such a thing can't exist? I'm going to think about this some more. I really find a lot of these solutions to be heavy handed, as you really want things to be polymorphic by default, and let the programmer or various compiler optimisations decide when they're only used monomorphically. A special keyword for killing polymorphic binding might work, but what's so wrong with just adding a type signature? - Cale -- sorry if anyone gets two copies of this, I thought I sent it, but later received notification that it wasn't sent.

On Sat, Jan 28, 2006 at 03:41:53PM -0500, Cale Gibbard wrote:
Is it really so impossible to implement typeclasses in a way which avoids this problem altogether? Perhaps the need for the MR in the first place is simply an indication that dictionary passing is not a complete solution to implementing typeclasses. It seems quite plausible that there should be an implementation which preserves polymorphism, and yet doesn't result in horrific inefficiency. Do we have a proof (or at least strong evidence) that such a thing can't exist?
interestingly enough, the monomorphism restriction in jhc actually should apply to all polymorphic values, independently of the type class system. x :: a x = x will transform into something that takes a type parameter and is hence not shared. I doubt this will cause a problem in practice since there arn't really any useful values of type forall a . a other than bottom. type classes don't introduce anything new at runtime that normal polymorphism didn't already require. An optimization that jhc implements which should be portable to other compilers is the 'type analysis' pass. it does a fixpoint iteration to determine every possible type every polymorhpic value is called at and then goes through and specializes all that are called at exactly one type, which is a surprisingly large amount. This is tied to the monomorphism restriction in that given foo :: Num a . a which is only used as an Int, should I turn it into a caf or give it a phantom argument to prevent sharing? I have not made up my mind on the issue... it would also be possible to require the compiler 'memoize' all top level bindings on their type parameter. then the problem goes away, but at the cost of hiding some machinery under the hood. however the type analysis pass mentioned above would often be able to discard of this 'under the hood' memoization and. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
An optimization that jhc implements which should be portable to other compilers is the 'type analysis' pass. it does a fixpoint iteration to determine every possible type every polymorhpic value is called at and then goes through and specializes all that are called at exactly one type, which is a surprisingly large amount. This is tied to the monomorphism restriction in that given foo :: Num a . a which is only used as an Int, should I turn it into a caf or give it a phantom argument to prevent sharing? I have not made up my mind on the issue...
I think most compilers have had this kind of option for quite a while. But how well works depends on the scope of it. With separate compilation (that really generates code) you can't really do it very well. Another (small) complication is that your the fixpoint iteration doesn't necessarily terminate. So you need a backup strategy. -- Lennart

John Meacham wrote:
interestingly enough, the monomorphism restriction in jhc actually should apply to all polymorphic values, independently of the type class system.
x :: a x = x
will transform into something that takes a type parameter and is hence not shared.
Interesting. I'd been wondering how you dealt with this case, and now it turns out that you don't. :-)
I doubt this will cause a problem in practice since there arn't really any useful values of type forall a . a other than bottom.
It could become an issue with something like churchNumerals :: [(a -> a) -> (a -> a)] churchNumerals = ... Maybe you could use a worker-wrapper transformation. churchNumerals' :: [(T -> T) -> (T -> T)] churchNumerals' = ... churchNumerals :: [(a -> a) -> (a -> a)] churchNumerals = /\ a . unsafeCoerce churchNumerals' The unsafeCoerce is scary, but it feels right to me. There is something genuinely unsavory about this kind of sharing, in Haskell or any other ML dialect. At least here it's out in the open. -- Ben
participants (13)
-
Andrew Pimlott
-
Ben Rudiak-Gould
-
Benjamin Franksen
-
Cale Gibbard
-
Johannes Waldmann
-
John Hughes
-
John Meacham
-
Lennart Augustsson
-
Philippa Cowderoy
-
Robert Dockins
-
Simon Marlow
-
Taral
-
Twan van Laarhoven