
I had promised myself not to propose anything that was not already implemented, tried, and tested, but I just can't resist bringing up a proposal I've made in the past to fix the monomorphism restriction. Maybe now is the time to do so. I know many will proclaim "just get rid of it", but consider this: without the M-R, some programs can run exponentially slower than you expect. This actually happened to me, which is how we discovered something of the sort was needed in the first place. But the current design is surely a wart. The fact is, Haskell has two different binding mechanisms--bind-by-name (used for overloaded definitions), and bind-by-need (monomorphic). Both are useful: bind-by-name lets us name overloaded expressions, while bind-by-need gives performance guarantees. The trouble is just the way we distinguish them--where the compiler is basically guessing from the form of a definition which one to use. Two problems that leads to: * You can't eta-convert definitions freely, if there is no type signature. We've all hit this one, where you write something like sum=foldr(+)0 and you can't export it, because it's monomorphic. * Definitions without a type-signature can change from polymorphic to monomorphic as a result of changes elsewhere in the program. Because the M-R applies only to overloaded definitions, then introducing, for example, an equality test in a function the definition calls can change its type, and make the M-R suddenly apply where it did not before. That can lead to unexpected errors. The solution I favour is simply to use *different syntax* for the two forms of binding, so that a definition is monomorphic, and computed at most once, if it uses the monomorphic binding operator, and polymorphic/overloaded, computed at each use, if it uses the other. Whether it's a function definition or not is irrelevant, as is whether or not it carries a type signature. The trick is finding good syntax. I suggest = for bind-by-name, and := for bind-by-need. (Some object that := "means" assignment--but come on, we're not reserving := for future use as assignment in Haskell, are we? Why should we give up a perfectly good symbol because it's used elsewhere to mean something else?). With this notation, = would be appropriate for function definitions, and := for most non-function definitions. It would be instantly clear where there was a possibility of repeated evaluation, and where not. The problem with making such a syntactic distinction is that, however it's done, many changes must be made to existing programs. Just because existing programs contain many bindings of each sort, there's no getting away from the fact that a syntactic distinction will force changes. In principle this could be automated, of course--not hard but somebody would have to do it. But perhaps it would be worth it, to eliminate probably the number one wart, and solve the problems above. I put it on the table, anyway. John

John Hughes wrote:
* You can't eta-convert definitions freely, if there is no type signature. ... * Definitions without a type-signature can change ...
(entering ironic mode, but not quite:) So, what about making type signatures mandatory, as the rest of the civilized world does happily for decades ... Yeah I know this would "break" some programs, but aren't these "broken" from the start because they are missing the easiest and safest and most effective way of documentation? If you say "writing out all type signatures is awkward", then exactly why? Because the type system is too complex? Then it should be fixed. I think it's not. Then perhaps because the types of the functions are too complex? Then these functions should be fixed (by refactoring, introducing helper type names, etc.). If this seems impossible, then the function itself probably *is* complex, and its type would give valuable information, and I don't see what a programmer (or a reader) benefits from a language that allows to omit this information. Respectfully submitted, -- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- ---- http://www.imn.htwk-leipzig.de/~waldmann/ -------

Dear all, Johannes Waldmann wrote:
So, what about making type signatures mandatory, as the rest of the civilized world does happily for decades ...
Given that explicit type signatures increasingly are required for dealing with other aspects (polymorphic recursion, rank 2-or-higher polymorphism, GADTs ...) that would seem reasonable. Personally, though, I have to admit that I've never had all that much problems with the M-R restriction in the first place. Probably because I do write top-level type signatures as soon as I get into serious programming. That said, I do find it convenient that type signatures can be omitted. And I wonder if this is a sufficiently significant problem to warrant breaking backwards compatibility in this respect. 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.

Johannes Waldmann wrote:
(entering ironic mode, but not quite:)
So, what about making type signatures mandatory, as the rest of the civilized world does happily for decades ...
If that's a serious proposal, then I'll argue against it--but do we really want to raise that question? One of the strengths of Haskell is that it supports both implicit and explicit typing well. John

On Thu, 26 Jan 2006, Johannes Waldmann wrote:
If this seems impossible, then the function itself probably *is* complex, and its type would give valuable information, and I don't see what a programmer (or a reader) benefits from a language that allows to omit this information.
For one, because that makes it possible to load it into an interpreter and be told the type. -- flippa@flippac.org A problem that's all in your head is still a problem. Brain damage is but one form of mind damage.

On Thu, Jan 26, 2006 at 10:59:22AM +0100, John Hughes wrote:
The fact is, Haskell has two different binding mechanisms--bind-by-name (used for overloaded definitions), and bind-by-need (monomorphic). Both are useful: bind-by-name lets us name overloaded expressions, while bind-by-need gives performance guarantees. The trouble is just the way we distinguish them--where the compiler is basically guessing from the form of a definition which one to use. [...] The solution I favour is simply to use *different syntax* for the two forms of binding, so that a definition is monomorphic, and computed at most once, if it uses the monomorphic binding operator, and polymorphic/overloaded, computed at each use, if it uses the other. Whether it's a function definition or not is irrelevant, as is whether or not it carries a type signature.
The trick is finding good syntax. I suggest = for bind-by-name, and := for bind-by-need. (Some object that := "means" assignment--but come on, we're not reserving := for future use as assignment in Haskell, are we? Why should we give up a perfectly good symbol because it's used elsewhere to mean something else?). With this notation, = would be appropriate for function definitions, and := for most non-function definitions. It would be instantly clear where there was a possibility of repeated evaluation, and where not.
The problem with making such a syntactic distinction is that, however it's done, many changes must be made to existing programs. Just because existing programs contain many bindings of each sort, there's no getting away from the fact that a syntactic distinction will force changes. In principle this could be automated, of course--not hard but somebody would have to do it. But perhaps it would be worth it, to eliminate probably the number one wart, and solve the problems above.
You're proposing that the =/:= distinction both decides whether constrained type variables are monomorphic and whether the binding should be implemented using sharing. If it only did the former (and the expectation was that all pattern bindings with unconstrained types used sharing), then existing legal programs would still be legal, and the examples that currently trip over the MR would be legal but inefficient. (Also, what does the shared/unshared distinction mean for functions?) What if one has mutually recursive bindings, some using = and some := ? Does monomorphism kick in if some of the variables in a binding group use :=, or would we just require that all bindings in the same group use the same binder? (At first I couldn't see why one would ever use := with function bindings, but perhaps that's the reason.)

On Thu, 26 Jan 2006, John Hughes wrote:
(Some object that := "means" assignment--but come on, we're not reserving := for future use as assignment in Haskell, are we? Why should we give up a perfectly good symbol because it's used elsewhere to mean something else?).
Programmers unfamiliar with Haskell but familiar with general programming ideas would be confused by it. I think this is a good reason to avoid (mis)use of this symbol. Quite a lot has been mentioned in various threads including this one about making sure that Haskell stays/becomes an easy/easier language to teach to undergraduates. However, there is a large and growing community of experienced programmers coming to Haskell and liking it, and we must keep them in mind too. A lot of them use the #haskell IRC channel as a resource, and as a regular there I have the impression that the numbers are on their way up quite rapidly. Cheers, Ganesh

On 26/01/06, John Hughes
I had promised myself not to propose anything that was not already implemented, tried, and tested, but I just can't resist bringing up a proposal I've made in the past to fix the monomorphism restriction. Maybe now is the time to do so.
I know many will proclaim "just get rid of it", but consider this: without the M-R, some programs can run exponentially slower than you expect. This actually happened to me, which is how we discovered something of the sort was needed in the first place. But the current design is surely a wart.
Do you have an example of such a program handy? Perhaps I'm just doing something stupid, but I can't seem to replicate the lack of sharing that's supposed to happen with the MR turned off in GHCi, so it's hard to play around with doing various translations by hand and seeing the results. Perhaps the optimiser is getting to the code and commoning things up? If this is the case, can't we just show that it always does so, or write that commoning into the translation, as suggested by Philippa, and forget about it? - Cale

On 28/01/06, Taral
On 1/28/06, Cale Gibbard
wrote: Do you have an example of such a program handy?
b = (x, x) where { x :: Num a => a; x = fromInteger 1 }
fromInteger is called twice.
--- mr.hs --- {-# OPTIONS_GHC -fno-monomorphism-restriction #-} import Debug.Trace b :: Num a => (a,a) b = (x,x) where x :: Num a => a x = (trace "x" . fromInteger) 1 main = print b ------------ cale@zaphod[~]$ ghci -fno-monomorphism-restriction mr.hs Loading package base-1.0 ... linking ... done. Compiling Main ( mr.hs, interpreted ) Ok, modules loaded: Main. *Main> :t b b :: (Num a) => (a, a) *Main> b (x 1,1) ------------ cale@zaphod[~]$ ghc -fno-monomorphism-restriction -o mr mr.hs && ./mr x (1,1) ----------- If x isn't being shared, then Debug.Trace at least seems incapable of resolving that fact. Let's try profiling: --- mr.hs, revised ----- {-# OPTIONS_GHC -fno-monomorphism-restriction #-} b :: Num a => (a,a) b = (x,x) where x :: Num a => a x = {-# SCC "x" #-} fromInteger 1 main = print b -------------- cale@zaphod[~]$ ghc -fno-monomorphism-restriction -prof -auto-all -o mr mr.hs && ./mr +RTS -p (1,1) cale@zaphod[~]$ cat mr.prof Sat Jan 28 18:21 2006 Time and Allocation Profiling Report (Final) mr +RTS -p -RTS total time = 0.00 secs (0 ticks @ 20 ms) total alloc = 17,972 bytes (excludes profiling overheads) COST CENTRE MODULE %time %alloc CAF GHC.Handle 0.0 48.2 CAF System.IO 0.0 1.4 CAF Main 0.0 50.3 individual inherited COST CENTRE MODULE no. entries %time %alloc %time %alloc MAIN MAIN 1 0 0.0 0.0 0.0 100.0 CAF Main 150 6 0.0 50.3 0.0 50.5 b Main 157 1 0.0 0.1 0.0 0.2 x Main 158 1 0.0 0.1 0.0 0.1 main Main 156 1 0.0 0.0 0.0 0.0 CAF System.IO 105 1 0.0 1.4 0.0 1.4 CAF GHC.Handle 103 3 0.0 48.2 0.0 48.2 ------- One entry to x. So where is this lack of sharing I keep hearing about? Even if I repeat these tests with -fno-cse, the results are the same. - Cale

Remove the type signature for b and you will see the loss of sharing. It mostly hurts people like John Hughes that don't have the energy to put in type signatures. ;) On the subject of type signatures, I don't want to make them mandatory, but I think they should be strongly encouraged. I don't buy the argument that they make refactoring programs that much harder. It's still very easy to do, the type checker will tell you exactly where. :) -- Lennart Cale Gibbard wrote:
On 28/01/06, Taral
wrote: On 1/28/06, Cale Gibbard
wrote: Do you have an example of such a program handy?
b = (x, x) where { x :: Num a => a; x = fromInteger 1 }
fromInteger is called twice.
--- mr.hs --- {-# OPTIONS_GHC -fno-monomorphism-restriction #-}
import Debug.Trace
b :: Num a => (a,a) b = (x,x) where x :: Num a => a x = (trace "x" . fromInteger) 1
main = print b ------------ cale@zaphod[~]$ ghci -fno-monomorphism-restriction mr.hs Loading package base-1.0 ... linking ... done. Compiling Main ( mr.hs, interpreted ) Ok, modules loaded: Main. *Main> :t b b :: (Num a) => (a, a) *Main> b (x 1,1) ------------ cale@zaphod[~]$ ghc -fno-monomorphism-restriction -o mr mr.hs && ./mr x (1,1) -----------
If x isn't being shared, then Debug.Trace at least seems incapable of resolving that fact.
Let's try profiling:
--- mr.hs, revised ----- {-# OPTIONS_GHC -fno-monomorphism-restriction #-}
b :: Num a => (a,a) b = (x,x) where x :: Num a => a x = {-# SCC "x" #-} fromInteger 1
main = print b -------------- cale@zaphod[~]$ ghc -fno-monomorphism-restriction -prof -auto-all -o mr mr.hs && ./mr +RTS -p (1,1) cale@zaphod[~]$ cat mr.prof Sat Jan 28 18:21 2006 Time and Allocation Profiling Report (Final)
mr +RTS -p -RTS
total time = 0.00 secs (0 ticks @ 20 ms) total alloc = 17,972 bytes (excludes profiling overheads)
COST CENTRE MODULE %time %alloc
CAF GHC.Handle 0.0 48.2 CAF System.IO 0.0 1.4 CAF Main 0.0 50.3
individual inherited COST CENTRE MODULE no. entries %time %alloc %time %alloc
MAIN MAIN 1 0 0.0 0.0 0.0 100.0 CAF Main 150 6 0.0 50.3 0.0 50.5 b Main 157 1 0.0 0.1 0.0 0.2 x Main 158 1 0.0 0.1 0.0 0.1 main Main 156 1 0.0 0.0 0.0 0.0 CAF System.IO 105 1 0.0 1.4 0.0 1.4 CAF GHC.Handle 103 3 0.0 48.2 0.0 48.2
-------
One entry to x. So where is this lack of sharing I keep hearing about? Even if I repeat these tests with -fno-cse, the results are the same.
- Cale _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://haskell.org/mailman/listinfo/haskell-prime

On 28/01/06, Lennart Augustsson
Remove the type signature for b and you will see the loss of sharing.
Nope, still not seeing it with either profiling or Debug.Trace. Also -- the type signature I gave was polymorphic, so what's the deal? If adding a polymorphic type signature fixes the problem, and a polymorphic type signature can be inferred, why not simply treat the source as if one had been written there?
It mostly hurts people like John Hughes that don't have the energy to put in type signatures. ;)
Well, sure. I don't think that we should see exponential blowup in complexity of some programs by leaving out type signatures (though if it was only in sufficiently rare cases, I could put up with it).
On the subject of type signatures, I don't want to make them mandatory, but I think they should be strongly encouraged. I don't buy the argument that they make refactoring programs that much harder. It's still very easy to do, the type checker will tell you exactly where. :)
Me too. It's nice to be able to write quick programs where you leave out the type signatures, but including them is always good for real code. I also think that type signatures (and the type system in general), makes it much easier to refactor code and work on code with which you're unfamiliar. - Cale

Oh, I guess I did one more change. I put b in a separate module. Your type signature isn't the most general, the most general is b :: (Num a, Num b) => (a, b) And that is the source of the problem. You need to pass two dictionaries. To keep sharing you'd need some very clever runtime machinery to find that the dictionaries are the same. -- Lennart Cale Gibbard wrote:
On 28/01/06, Lennart Augustsson
wrote: Remove the type signature for b and you will see the loss of sharing.
Nope, still not seeing it with either profiling or Debug.Trace. Also -- the type signature I gave was polymorphic, so what's the deal? If adding a polymorphic type signature fixes the problem, and a polymorphic type signature can be inferred, why not simply treat the source as if one had been written there?
It mostly hurts people like John Hughes that don't have the energy to put in type signatures. ;)
Well, sure. I don't think that we should see exponential blowup in complexity of some programs by leaving out type signatures (though if it was only in sufficiently rare cases, I could put up with it).
On the subject of type signatures, I don't want to make them mandatory, but I think they should be strongly encouraged. I don't buy the argument that they make refactoring programs that much harder. It's still very easy to do, the type checker will tell you exactly where. :)
Me too. It's nice to be able to write quick programs where you leave out the type signatures, but including them is always good for real code. I also think that type signatures (and the type system in general), makes it much easier to refactor code and work on code with which you're unfamiliar.
- Cale

Aha, okay. Yeah, I can reproduce that now, and it makes good sense
what's going on. It is in fact quite sensible that x be evaluated
twice with that sort of polymorphism.
Hmm... however, could we not assign to each instance a unique
identifier which could be compared? Say a cryptographic hash of the
source code for the instance? (Which of course would never be exposed
to the user.) That should be enough to tell them apart. The
translation would then partition the work according to the incoming
instances, and share all computation possible.
- Cale
On 28/01/06, Lennart Augustsson
Oh, I guess I did one more change. I put b in a separate module.
Your type signature isn't the most general, the most general is b :: (Num a, Num b) => (a, b) And that is the source of the problem. You need to pass two dictionaries. To keep sharing you'd need some very clever runtime machinery to find that the dictionaries are the same.
-- Lennart
Cale Gibbard wrote:
On 28/01/06, Lennart Augustsson
wrote: Remove the type signature for b and you will see the loss of sharing.
Nope, still not seeing it with either profiling or Debug.Trace. Also -- the type signature I gave was polymorphic, so what's the deal? If adding a polymorphic type signature fixes the problem, and a polymorphic type signature can be inferred, why not simply treat the source as if one had been written there?
It mostly hurts people like John Hughes that don't have the energy to put in type signatures. ;)
Well, sure. I don't think that we should see exponential blowup in complexity of some programs by leaving out type signatures (though if it was only in sufficiently rare cases, I could put up with it).
On the subject of type signatures, I don't want to make them mandatory, but I think they should be strongly encouraged. I don't buy the argument that they make refactoring programs that much harder. It's still very easy to do, the type checker will tell you exactly where. :)
Me too. It's nice to be able to write quick programs where you leave out the type signatures, but including them is always good for real code. I also think that type signatures (and the type system in general), makes it much easier to refactor code and work on code with which you're unfamiliar.
- Cale

Yes, you can do something to regain sharing. That's what I meant by having some clever runtime machinery. But it's rather complex for what the problem at hand is. -- Lennart Cale Gibbard wrote:
Aha, okay. Yeah, I can reproduce that now, and it makes good sense what's going on. It is in fact quite sensible that x be evaluated twice with that sort of polymorphism.
Hmm... however, could we not assign to each instance a unique identifier which could be compared? Say a cryptographic hash of the source code for the instance? (Which of course would never be exposed to the user.) That should be enough to tell them apart. The translation would then partition the work according to the incoming instances, and share all computation possible.
- Cale
On 28/01/06, Lennart Augustsson
wrote: Oh, I guess I did one more change. I put b in a separate module.
Your type signature isn't the most general, the most general is b :: (Num a, Num b) => (a, b) And that is the source of the problem. You need to pass two dictionaries. To keep sharing you'd need some very clever runtime machinery to find that the dictionaries are the same.
-- Lennart
Cale Gibbard wrote:
On 28/01/06, Lennart Augustsson
wrote: Remove the type signature for b and you will see the loss of sharing.
Nope, still not seeing it with either profiling or Debug.Trace. Also -- the type signature I gave was polymorphic, so what's the deal? If adding a polymorphic type signature fixes the problem, and a polymorphic type signature can be inferred, why not simply treat the source as if one had been written there?
It mostly hurts people like John Hughes that don't have the energy to put in type signatures. ;)
Well, sure. I don't think that we should see exponential blowup in complexity of some programs by leaving out type signatures (though if it was only in sufficiently rare cases, I could put up with it).
On the subject of type signatures, I don't want to make them mandatory, but I think they should be strongly encouraged. I don't buy the argument that they make refactoring programs that much harder. It's still very easy to do, the type checker will tell you exactly where. :)
Me too. It's nice to be able to write quick programs where you leave out the type signatures, but including them is always good for real code. I also think that type signatures (and the type system in general), makes it much easier to refactor code and work on code with which you're unfamiliar.
- Cale

Hmm... however, could we not assign to each instance a unique identifier which could be compared? Say a cryptographic hash of the source code for the instance? (Which of course would never be exposed to the user.) That should be enough to tell them apart. By the way, this is the method used by Computer Algebra Systems. However, it is really unclear if the cost is worth it, in memory as well as in CPU time. When you are doing a lot of "expression manipulation",
Cale Gibbard wrote: this seems worth it, but for more general program execution, it seems not to be. Personally I think that this ought to be resolved by static means -- and yes, by the linker, as it can't be done properly earlier. Jacques

Jacques Carette wrote:
Personally I think that this ought to be resolved by static means -- and yes, by the linker, as it can't be done properly earlier.
But there are cases that cannot be resolved statically. On the other hand, they are probably rare enough to ignore. -- Lennart

On Sun, 29 Jan 2006, Lennart Augustsson wrote:
Jacques Carette wrote:
Personally I think that this ought to be resolved by static means -- and yes, by the linker, as it can't be done properly earlier.
But there are cases that cannot be resolved statically. On the other hand, they are probably rare enough to ignore.
Or to flag up a compiler and/or linker warning for those who request them? -- flippa@flippac.org Sometimes you gotta fight fire with fire. Most of the time you just get burnt worse though.

Hmmm, maybe a warning is the best solution in general. Even without trying any link time resolution. Given how hard Cale had to work to reproduce it, I think it's a rare problem. Maybe someone who knows the innards of ghc could make a quick hack that turns on the M-R and warns when there's actually sharing being lost. Philippa Cowderoy wrote:
On Sun, 29 Jan 2006, Lennart Augustsson wrote:
Jacques Carette wrote:
Personally I think that this ought to be resolved by static means -- and yes, by the linker, as it can't be done properly earlier.
But there are cases that cannot be resolved statically. On the other hand, they are probably rare enough to ignore.
Or to flag up a compiler and/or linker warning for those who request them?

On 29/01/06, Lennart Augustsson
Hmmm, maybe a warning is the best solution in general. Even without trying any link time resolution.
Given how hard Cale had to work to reproduce it, I think it's a rare problem. Maybe someone who knows the innards of ghc could make a quick hack that turns on the M-R and warns when there's actually sharing being lost.
Yeah, this is a good idea, I wonder how often this actually comes up. I'd had trouble reproducing it since I accidentally gave 'b' a type signature which wasn't sufficiently polymorphic to make the problem occur. Inside a module, optimisation to determine if sharing was needed is surely possible. Having the compiler produce specialised code to handle cases which recover sharing from inside a single module seems practical enough to do. Across module boundaries, if whole-program optimisation can't be applied to restore sharing somehow, you'd need extra runtime support - and you're right, that does seem like it may be a little heavy. How I see it, it would basically amount to a polymorphic value becoming a lookup in a memo map from instances at which it's been computed to (weak pointers to?) final values, together with a fall-through to the code which uses the dictionary to compute the value, and then inserts a new entry into the map before returning normally. Whether all that's really worth it, we should probably look into. How many ordinary programs do we have sitting around that run into this sharing problem? Anyway, I see mandating the MR as somewhat ugly, while including it as a possible compiler optimisation seems okay. Since a smart enough compiler/runtime could make sure that the problems the MR solves are nonexistent anyway, do we really want to include it in the standard? - Cale

Lennart Augustsson wrote:
Jacques Carette wrote:
Personally I think that this ought to be resolved by static means -- and yes, by the linker, as it can't be done properly earlier.
But there are cases that cannot be resolved statically. On the other hand, they are probably rare enough to ignore. There will always be some things that are impossible to do statically - but we should still strive to do as many as possible, even if we are forced to be incomplete about it. As long as the cases that can't be done are relatively easy to define and occur rarely, that seems like a good compromise to me.
Jacques

There are a whole lot of ways to ruin the performance of haskell programs that are a lot more subtle than the MR restriction. I don't see why we deem this particular one, especially when it is easily solved by adding a type signature, of special enough import to change the language over. However, If we must have a new syntax then another possibility is that since pattern matching is already monomorhpic, we can have the 'unary tuple' pattern mean monomorphic without using any new syntax. (x) = fromInteger 3 which sort of looks like a unary tuple match and makes it very clear that only values (and not functions) may be bound in this manner and the fact that it is shared falls naturally from thinking of it as being pulled out of a data structure. I would much prefer something like this as opposed to a new operator. we are used to = behaving differently when pattern matching vs naming. John -- John Meacham - ⑆repetae.net⑆john⑈

Having thought about this for a while I'm coming down on the side of keeping some sort of monomorphism restriction, for the following reason. It's hard to bound the space consumption of a Haskell program, but easy to bound its time consumption: its asymptotic runtime will be the same as or better than an "equivalent" ML program, because each bit of code gets evaluated at most once for every time that ML would evaluate it. Even optimistic evaluation preserves this property. Dropping the monomorphism restriction would break it. I understand the theoretical appeal of polymorphism by default, but there's also a lot of theoretical appeal to dropping thunk updating, and in practice I dread both ideas. I don't want to have to think, every time I bind a variable, about whether it might be evaluated more than once. I also don't want to have to track down multiple-evaluation cases with runtime profiling. I want the compiler to notice these problems for me. So if polymorphism were the default, I would end up defensively requesting monomorphism almost all the time. Therefore I'm strongly opposed to any proposal that requires a type signature for monomorphism, because it would create a large amount of work for me. I'm moderately opposed to the (x) = ... proposal, because it would uglify my code. I'm moderately in favor of John Hughes's original := proposal, because it seems less ugly. Now, I rarely run into the monomorphism restriction as it stands because I rarely write point-free code. And I suspect this is what the debate is really about: it's the point-free people who usually want polymorphism versus the, uh, pointwise people who usually don't. For myself I'd be happiest keeping the monomorphism restriction as it now stands, but maybe John Hughes's proposal is the best compromise between the two camps (assuming they exist outside my imagination). -- Ben
participants (12)
-
Ben Rudiak-Gould
-
Cale Gibbard
-
Ganesh Sittampalam
-
Henrik Nilsson
-
Jacques Carette
-
Johannes Waldmann
-
John Hughes
-
John Meacham
-
Lennart Augustsson
-
Philippa Cowderoy
-
Ross Paterson
-
Taral