Re: [Haskell] -fno-monomorphism-restriction makes type-inference ambiguous?

2006-02-27 Thread John Meacham
On Mon, Feb 27, 2006 at 04:42:32PM +0100, Johannes Waldmann wrote: > Implicit parameters are *evil*. They seem to simplify programs > but they make reasoning about them much harder. Indeed. We really need some big caveats in the manual. I find a lot of new users think they are what they need and j

Re: [Haskell] -fno-monomorphism-restriction makes type-inference ambiguous?

2006-02-27 Thread Johannes Waldmann
Implicit parameters are *evil*. They seem to simplify programs but they make reasoning about them much harder. To an extent, they can be simulated with type classes, because dictionaries are also implicit (you don't see them in the code but you see them in the type declaration - same as for implic

[Haskell] -fno-monomorphism-restriction makes type-inference ambiguous?

2006-02-27 Thread Eike Scholz
Hi, thanks for the last help and hints. I have encountered an other problem, and again I don't quite understand the reason why I get the results I get. ghci seems to infer different types for the same expression. Consider that I have disabled the monomorphism restriction in module AG

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
I wrote: > My solution *is* the Right Thing. :-) What I meant is: it always preserves the validity of inlining, it always preserves sharing, and it rejects otherwise-correct programs only in situations which are (I expect) uncommon in practice. -- Ben ___

Re: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
I wrote: > Exactly the same rule should apply to implicit parameters. In the case of > implicit parameters, safety is ensured if in every use of the bound > variable, its implicit parameter refers to the same explicit binding of > that parameter. For example, the expression > > let g = ?x i

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
ome clear. > Comments from TcSimplify > > Question 3: monomorphism > ~~~~ > There's a nasty corner case when the monomorphism restriction bites: > > z = (x::Int) + ?y > > The argument above suggests that we *must* generalise &g

Re: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
though it would be rejected if one of the 1s were changed to something else. Cases like this would be rare, though, and it's not clear that programs of this type should really be accepted anyway, since the safety is rather fragile. None of these complications threatens the overall v

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-05 Thread Simon Peyton-Jones
| I just figured out why the monomorphism restriction interacts so weirdly | with implicit parameters, and how to fix it. I'm afraid that I have not read all of the recent exciting flood of messages carefully, but I do remember that the interaction of the monomorphism restriction with imp

Solution to the monomorphism restriction/implicit parameter problem

2003-08-05 Thread Ben Rudiak-Gould
I just figured out why the monomorphism restriction interacts so weirdly with implicit parameters, and how to fix it. We all know that when the monomorphism restriction is turned on, the following doesn't work: let f = (<) in (f 1 2, f 'a' 'b') On the other h

Re: Monomorphism, monomorphism...

2001-10-24 Thread Marcin 'Qrczak' Kowalczyk
Wed, 24 Oct 2001 10:36:22 +0200, Hannah Schroeter <[EMAIL PROTECTED]> pisze: > Why not create a dictionary record while compiling the associated > instance (which may, by the H'98 definition, occur only once in > the program)? Instances with contexts are commonly represented as functions which m

Re: Monomorphism, monomorphism...

2001-10-24 Thread Lennart Augustsson
Hannah Schroeter wrote: > I don't think so. Why not create a dictionary record while compiling > the associated instance (which may, by the H'98 definition, occur > only once in the program)? One problem is that certain Haskell programs need an unbounded number of instances. -- Lennart

Re: Monomorphism, monomorphism...

2001-10-24 Thread Hannah Schroeter
Hello! On Mon, Oct 08, 2001 at 07:38:09PM +, Marcin 'Qrczak' Kowalczyk wrote: > Mon, 8 Oct 2001 11:35:48 +0200, Hannah Schroeter <[EMAIL PROTECTED]> pisze: > > Now, with the typical dictionary implementation of type classes, > > this wouldn't really be too difficult. > Dictionaries would ha

Re: Monomorphism, monomorphism...

2001-10-10 Thread Ashley Yakeley
At 2001-10-10 03:59, Marcin 'Qrczak' Kowalczyk wrote: >We need some type T such that it's possible to define a family of >functions for arbitrary choices of A: >upA :: A -> T >downA :: T -> Maybe A >satisfying downA (upA a) = Just a. We want to choose the type for T >before deciding the

Re: Monomorphism, monomorphism...

2001-10-10 Thread Carl R. Witty
"Marcin 'Qrczak' Kowalczyk" <[EMAIL PROTECTED]> writes: > 09 Oct 2001 13:55:04 -0700, Carl R. Witty <[EMAIL PROTECTED]> pisze: > > > The TREX paper from Mark Jones and Benedict Gaster (I hope I > > have the names right) had both extensible records and extensible > > variants (extensible variants

Re: Monomorphism, monomorphism...

2001-10-10 Thread Marcin 'Qrczak' Kowalczyk
09 Oct 2001 13:55:04 -0700, Carl R. Witty <[EMAIL PROTECTED]> pisze: > The TREX paper from Mark Jones and Benedict Gaster (I hope I > have the names right) had both extensible records and extensible > variants (extensible variants being what you would need to implement > downcasts), I don't thin

Re: Monomorphism, monomorphism...

2001-10-09 Thread Carl R. Witty
"Marcin 'Qrczak' Kowalczyk" <[EMAIL PROTECTED]> writes: > Since OO languages often use subtypes to emulate constructors of > algebraic types, they need downcasts. In Haskell it's perhaps less > needed but it's a pity that it's impossible to translate an OO scheme > which makes use of downcasts in

Re: Extensible downcasts impossible in Haskell? (was Re: Monomorphism, monomorphism...)

2001-10-09 Thread Marcin 'Qrczak' Kowalczyk
Tue, 9 Oct 2001 10:50:19 +1300, Tom Pledger <[EMAIL PROTECTED]> pisze: > I'm curious about this impossibility. > > - Is it well known? If so, would someone please refer me to a paper > or posting which explains it? I don't know. I'm not even sure if some clever encoding couldn't express

Extensible downcasts impossible in Haskell? (was Re: Monomorphism, monomorphism...)

2001-10-08 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: : | Since OO languages often use subtypes to emulate constructors of | algebraic types, they need downcasts. In Haskell it's perhaps less | needed but it's a pity that it's impossible to translate an OO | scheme which makes use of downcasts into Haskell in an

Re: Monomorphism, monomorphism...

2001-10-08 Thread Marcin 'Qrczak' Kowalczyk
Mon, 8 Oct 2001 11:35:48 +0200, Hannah Schroeter <[EMAIL PROTECTED]> pisze: > Now, with the typical dictionary implementation of type classes, > this wouldn't really be too difficult. Dictionaries would have to be make hashable and comparable. For a sane semantics you can't compare their identit

Re: Monomorphism, monomorphism...

2001-10-08 Thread Hannah Schroeter
Hello! On Sun, Oct 07, 2001 at 11:29:09AM +, Marcin 'Qrczak' Kowalczyk wrote: > [...] > >Shouldn't the compiler be able to limit the recomputations to > >one per instance of the class? > It would require very unusual implementation. Currently the compiler > doesn't need to build dic

Re: Monomorphism, monomorphism...

2001-10-07 Thread Marcin 'Qrczak' Kowalczyk
alking about the case '(var1, var2) = expr', right? That's >because var1 and var2 cannot have different contexts? They can, caused by different sets of type variables present in types of var1 and var2: (x, y) = let z = read "[10,20]" in (z, show z) Here x :: Read

Re: Monomorphism, monomorphism...

2001-10-06 Thread Juan Carlos Arévalo Baeza
n like "let g = isNil" >>  there cannot be any compelling reason to give "g" any type >>  different than the type of "isNil". > >There are two reasons for the monomorphism restriction: > >- isNil (or any value with a non-empty context in its ty

Re: Monomorphism, monomorphism...

2001-10-06 Thread Karl-Filip Faxen
Hi! Marcin wrote: > Juan Carlos Arévalo Baeza wrote: >> Karl-Filip wrote: >>>- a -> Bool (without quantification and with "IsNil a" among the >>> predicates). >> >>This is something I didn't understand either. Which predicates? > >I think "isNil a" goes to the context of the whole expressio

Re: Monomorphism, monomorphism...

2001-10-06 Thread Marcin 'Qrczak' Kowalczyk
ot;g" cannot be >"g :: => " unless the context is explicitly given? Yes. >Hmmm... This still sounds like nonsensical (as in counterintuitive >and artificial) to me. In a definition like "let g = isNil" >there cannot be any compelling reason to gi

Monomorphism, monomorphism...

2001-10-05 Thread Juan Carlos Arévalo Baeza
On Fri, 05 Oct 2001 21:25:57 +0200, Karl-Filip Faxen wrote: >The monomorphism restriction goes like this in my inference rules: > >If a declaration group contains a pattern binding with a nonvariable pattern >or one where there is no type signature for the variable, then the conte

re: Monomorphism Restriction

2001-06-10 Thread Bernard James POPE
Ashley Yakeley, Seattle WA, writes: > Is there a point to the "monomorphism restriction" in GHC and Hugs? In > practice, all it seems to mean is "occasionally require unnecessary > explicit type signatures". I think the point is made clearly enough in section 4.5

Monomorphism Restriction

2001-06-09 Thread Ashley Yakeley
Is there a point to the "monomorphism restriction" in GHC and Hugs? In practice, all it seems to mean is "occasionally require unnecessary explicit type signatures". -- Ashley Yakeley, Seattle WA ___ Haskell mailing list [E

Re: polymorphic recursion (was: Re: Implict parameters and monomorphism)

2001-05-06 Thread Fergus Henderson
On 06-May-2001, Bernard James POPE <[EMAIL PROTECTED]> wrote: > > If you applied the Mercury algorithm to Haskell (ie used fixed point iteration > to search for a type, rather than requiring a type annotation), would > the new type inference algorithm accept/reject the same programs as the > exi

polymorphic recursion (was: Re: Implict parameters and monomorphism)

2001-05-05 Thread Bernard James POPE
> Fergus Henderson wrote: > In contrast, Haskell uses a type inference algorithm > which sometimes infers what I would call wrong answers: > types which are less general that can be obtained with an explicit > type declaration. These types might not be what the programmer had > intended, and thi

Re: Implict parameters and monomorphism

2001-05-05 Thread Fergus Henderson
On 04-May-2001, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > Lennart Augustsson [mailto:[EMAIL PROTECTED]] wrote: > | It is not at all surprising that you can write this. > | Originally type signatures only allowed you to put a > | signature that was more specific. > | Polymorhic recursion o

Re: Implict parameters and monomorphism

2001-05-04 Thread Marcin 'Qrczak' Kowalczyk
Fri, 4 May 2001 11:27:07 -0700, John Meacham <[EMAIL PROTECTED]> pisze: > My idea was to allow '_' to be used in type signatures and represent > any type. I like it. There were also proposals for '..'. It would be useful in cases analogous to this: import IArray import MArray f:: (IArray a e,

Re: Implict parameters and monomorphism

2001-05-04 Thread John Meacham
I have thought about this too. omission of type signatures seems to be an effective catalyst for code re-use yet this benefit is rarely emphasised. I was thinking about ways to make it easier and toyed around with allowing 'unkowns' in type declarations to allow you to specify only the important p

Re: Implict parameters and monomorphism

2001-05-04 Thread Mieszko Lis
On Fri, May 04, 2001 at 09:27:51AM +0200, John Hughes wrote: > One good reason for NOT giving inferrable type signatures is that > including them makes programs less modifiable: a small local change, such as > adding a parameter to a type, may force a large number of consequential > change

RE: Implict parameters and monomorphism

2001-05-04 Thread Simon Peyton-Jones
3 May 2001 15:24 | To: [EMAIL PROTECTED]; [EMAIL PROTECTED] | Cc: [EMAIL PROTECTED] | Subject: Re: Implict parameters and monomorphism | | | OK, so since noone liked my original example here's another | one. It involves no defaulting and no classes in the funny | function definition. | | --

Re: Implict parameters and monomorphism

2001-05-04 Thread Marcin 'Qrczak' Kowalczyk
Fri, 4 May 2001 09:27:51 +0200 (MET DST), John Hughes <[EMAIL PROTECTED]> pisze: > One good reason for NOT giving inferrable type signatures is that > including them makes programs less modifiable: a small local change, > such as adding a parameter to a type, may force a large number of > consequ

Re: Implict parameters and monomorphism

2001-05-04 Thread John Hughes
> Except, of course, for top level bindings which is where the > monomorphism restriction is usually most noticable. Right, but an explicit monomorphic type signature would ensure that it's computed once. Type signatures on toplevel bindings

Re: Implict parameters and monomorphism

2001-05-03 Thread John Launchbury
This whole monomorphism-restriction debate was one that we had when we were writing the implicit parameters paper. We noted the dire impact of the monomorphism restriction, and commented upon it. On reviewing the whole issue again I am forced again to conclude: There Is No Satisfactory

Re: Implict parameters and monomorphism

2001-05-03 Thread Marcin 'Qrczak' Kowalczyk
Thu, 3 May 2001 15:26:38 -0600, Alastair Reid <[EMAIL PROTECTED]> pisze: >> You can always use 'case' instead of 'let' for variable bindings. > > Except, of course, for top level bindings which is where the > monomorphism restriction is usuall

RE: Implict parameters and monomorphism

2001-05-03 Thread Alastair Reid
> You can always use 'case' instead of 'let' for variable bindings. Except, of course, for top level bindings which is where the monomorphism restriction is usually most noticable. > I would remove the monomorphism restriction, [...] This seems to be a pretty common

Re: Implict parameters and monomorphism

2001-05-03 Thread Marcin 'Qrczak' Kowalczyk
Wed, 2 May 2001 10:51:58 +0200 (MET DST), John Hughes <[EMAIL PROTECTED]> pisze: > Breaking the monomorphism restriction in ANY case makes both space > and time cost of evaluation unpredictable, and brittle when program > changes elsewhere introduce or remove an implicit para

Re: Implict parameters and monomorphism

2001-05-03 Thread Lennart Augustsson
OK, so since noone liked my original example here's another one. It involves no defaulting and no classes in the funny function definition. -- Here's the type signature that makes a difference. --fun :: a -> Char fun x = const (fun x) (fun True) fix f = let x = f x in x class C a where m ::

Re: Implict parameters and monomorphism

2001-05-03 Thread C.Reinke
> But most importantly, this was a bad example. There was a much better > one posted on this mailing list a while ago. Does anyone remember it? > > -- Lennart Perhaps I should mention a useful application of this game, somewhat unhelpfully named "Representative thingies" in my Haskell cor

Re: Implict parameters and monomorphism

2001-05-03 Thread Marcin 'Qrczak' Kowalczyk
g to visible definitions, to Int or Integer here, and from another module it is not known that the types have been ambiguous, so constraints from non-Haskell-98 classes can't stop the defaulting. This is an argument for removing that part of the defaulting rule. Or for removing the monomor

Re: Implict parameters and monomorphism

2001-05-03 Thread C.Reinke
> > > Try this program: > > > -- Try commenting out this type signature. > > > fun:: (Num a) => a -> Int > > Defaulting applies only when all classes involved are Haskell 98. > > First, I cannot parse that sentence, but I assume you mean when all > classes are Prelude classes. > Second, I'm pret

Re: Implict parameters and monomorphism

2001-05-03 Thread Andreas Rossberg
Lennart Augustsson wrote: > > But most importantly, this was a bad example. There was a much better > one posted on this mailing list a while ago. Does anyone remember it? No, but this should do it: data T = T Int instance Show T where show (T n) = show n instance Eq instance Num T

Re: Implict parameters and monomorphism

2001-05-03 Thread C.Reinke
> > Try this program: > > -- Try commenting out this type signature. > > fun:: (Num a) => a -> Int > Defaulting applies only when all classes involved are Haskell 98. > hbc, nhc98 and Hugs are not conforming. Seems you're right (all classes for the ambiguous type variable need to be from prelude

Re: Implict parameters and monomorphism

2001-05-03 Thread Lennart Augustsson
Marcin 'Qrczak' Kowalczyk wrote: > Thu, 03 May 2001 06:29:35 -0400, Lennart Augustsson <[EMAIL PROTECTED]> >pisze: > > > Try this program: > > -- Try commenting out this type signature. > > fun:: (Num a) => a -> Int > > Test.hs:7: > Ambiguous type variable(s) `a' in the constraint `Num a' >

Re: Implict parameters and monomorphism

2001-05-03 Thread Marcin 'Qrczak' Kowalczyk
Thu, 03 May 2001 06:29:35 -0400, Lennart Augustsson <[EMAIL PROTECTED]> pisze: > Try this program: > -- Try commenting out this type signature. > fun:: (Num a) => a -> Int Test.hs:7: Ambiguous type variable(s) `a' in the constraint `Num a' arising from use of `fun' at Test.hs:7 In t

Re: Implict parameters and monomorphism

2001-05-03 Thread Lennart Augustsson
Simon Peyton-Jones wrote: > | a) That adding a type signature can change the dynamic semantics > | of the program. This would be the first and only > | occurrence of > | such behaviour. > | > | At present, adding a type signature changes both the static > | semantics an

Re: Implict parameters and monomorphism

2001-05-03 Thread Lennart Augustsson
Simon Peyton-Jones wrote: > John: just to check, you do realise that (B) means > > a) That adding a type signature can change the dynamic semantics > of the program. This would be the first and only occurrence of > such behaviour. Not so, there are already Haskell program that give a di

RE: Implict parameters and monomorphism

2001-05-03 Thread Simon Peyton-Jones
| a) That adding a type signature can change the dynamic semantics | of the program. This would be the first and only | occurrence of | such behaviour. | | At present, adding a type signature changes both the static | semantics and the cost of running a program That

RE: Implict parameters and monomorphism

2001-05-03 Thread John Hughes
John: just to check, you do realise that (B) means a) That adding a type signature can change the dynamic semantics of the program. This would be the first and only occurrence of such behaviour. At present, adding a type signature changes both the static

Re: Implict parameters and monomorphism

2001-05-03 Thread Jeffrey R. Lewis
Simon Peyton-Jones wrote: > | As far as what one would `expect', it's in the very nature of > | dynamic binding that it makes the meaning of an expression > | depend on its context. I for one would certainly not expect > | that inlining a definition bound to such an > | expression should preserve

Re: Implict parameters and monomorphism

2001-05-03 Thread John Hughes
choice of evaluation order, which makes space leaks come and go on different compilers. In any case, I don't buy the argument that because reasoning about costs is already problematic in Haskell, it doesn't matter if we make it even harder...! > Breaking the monomorphism restr

Re: Implict parameters and monomorphism

2001-05-03 Thread John Hughes
But a term with an "implicit" argument is a function no matter how you turn it, you just don't write the argument explicitely. I don't buy that. You could equally well say a term with a free variable is a "function" (of the environment): sure it is, but if it's bound with a let t

RE: Implict parameters and monomorphism

2001-05-02 Thread Simon Peyton-Jones
iour. (For ordinary type classes, the monomorphism restriction will reject some programs that would otherwise be well typed; for implicit parameters, (B) will accept the program but with --- potentially a different meaning.) b) That whether or not a definition is unconditio

Re: Implict parameters and monomorphism

2001-05-02 Thread Rishiyur S. Nikhil
John Hughes wrote: > ... Function bodies are clearly evaluated many times, once for each > call, but non-function bindings should be evaluated at most once to respect > call-by-need semantics. Isn't this a very fragile distinction? It seems so susceptible to routine program transformations by

Re: Implict parameters and monomorphism

2001-05-02 Thread Erik Meijer
ll-by-need semantics. Breaking the monomorphism restriction in ANY case > makes both space and time cost of evaluation unpredictable, and brittle when > program changes elsewhere introduce or remove an implicit parameter. It isn't > good enough to say `the chances are' that a prog

Re: Implict parameters and monomorphism

2001-05-02 Thread Andreas Rossberg
t specify any execution model the MR looks rather arbitrary to me. > Breaking the monomorphism restriction in ANY case makes both > space and time cost of evaluation unpredictable, and brittle > when program changes elsewhere introduce or remove an implicit > parameter. It isn't good

Re: Implict parameters and monomorphism

2001-05-02 Thread John Hughes
(B) Monomorphism restriction "wins" Bindings that fall under the monomorphism restriction can't be generalised Always generalise over implicit parameters *except* for bindings that fall under the monomorph

RE: Implict parameters and monomorphism

2001-04-30 Thread Simon Peyton-Jones
Jeff Thanks for your detailed reply. | In other words, the monomorphism restriction converts certain | let bindings to lambda bindings. But this approach pre-supposes that the monomorphism restriction takes priority over the "must generalise implicit parameters" rule. Once you

Re: Implict parameters and monomorphism

2001-04-26 Thread kahl
Jeffrey R. Lewis <[EMAIL PROTECTED]> argued that the monomorphism restriction enabled translations of let-bindungs into lambda-bindings: > > let z = x + ?y in z+z > > > > [...] > > The example above becomes: > (\z -> z + z) (x + ?y)

Re: Implict parameters and monomorphism

2001-04-25 Thread Jeffrey R. Lewis
Simon Peyton-Jones wrote: > This is a long message about the design of implicit parameters. > In particular, it is about the interaction of the monomorphism > restriction with implicit parameters. This issue was discussed > in the original implicit-parameter paper, but I wanted t

Re: Implict parameters and monomorphism

2001-04-25 Thread kahl
nt) + ?y > [...] > > Conclusion: the above type signature is illegal. You'll get a message > of the form "could not deduce (?y::Int) from ()". Must be so. > Question 3: monomorphism > ~~~~ [...] > > Possibl

Re: Implict parameters and monomorphism

2001-04-25 Thread Robert Ennals
> On Wed, 25 Apr 2001, Robert Ennals wrote: > > > Thus if we want to "inherit" our implicit paramater, we would have: > > > > f ?y x = (x :: Int) + ?y > > I like the current solution better. They are called "implicit parameters" > because they are, well, implicit :-) The semantics is still imp

Re: Implict parameters and monomorphism

2001-04-25 Thread Marcin 'Qrczak' Kowalczyk
On Wed, 25 Apr 2001, Robert Ennals wrote: > Thus if we want to "inherit" our implicit paramater, we would have: > > f ?y x = (x :: Int) + ?y I like the current solution better. They are called "implicit parameters" because they are, well, implicit :-) -- Marcin 'Qrczak' Kowalczyk __

Re: Implict parameters and monomorphism

2001-04-25 Thread Marcin 'Qrczak' Kowalczyk
25 Apr 2001 07:18:50 GMT, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> pisze: > Why would it magically turn into an ordinary identifier for inner > scopes? It dynamically appears in each place it is used. In other words since ?x is legal in an inner scope no matter whether it appears in an oute

Re: Implict parameters and monomorphism

2001-04-25 Thread Robert Ennals
the "z" example, we get z ?y = (x::Int) + ?y This still gives us a type of z :: (?y :: Int) => Int but the "function-like" nature is now explicit, and thus IMHO, in this case there is a more reasonable argument for dropping the monomorphism restriction. If I write

Re: Implict parameters and monomorphism

2001-04-25 Thread Marcin 'Qrczak' Kowalczyk
Tue, 24 Apr 2001 22:51:41 -0400, Dylan Thurston <[EMAIL PROTECTED]> pisze: > It seems desirable to provide some way to allow either possible answer > to Question 1 (i.e., dynamically scoped or statically scoped ?y). You can bind its value to a statically scoped variable. IMHO it shoult not be s

Re: Implict parameters and monomorphism

2001-04-25 Thread Marcin 'Qrczak' Kowalczyk
Tue, 24 Apr 2001 16:04:54 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > Choice (C) really says "the monomorphism restriction doesn't apply > to implicit parameters". Which is fine, but remember that every > innocent binding 'x = ...' that men

Re: Implict parameters and monomorphism

2001-04-24 Thread Dylan Thurston
On Tue, Apr 24, 2001 at 04:04:54PM -0700, Simon Peyton-Jones wrote: > Question 1: can we "inherit" implicit parameters > > Consider this: > > f x = (x::Int) + ?y > ... > f :: Int -> Int > [versus] > f :: (?y::Int) => Int -> Int >

Implict parameters and monomorphism

2001-04-24 Thread Simon Peyton-Jones
This is a long message about the design of implicit parameters. In particular, it is about the interaction of the monomorphism restriction with implicit parameters. This issue was discussed in the original implicit-parameter paper, but I wanted to articulate it afresh and propose some design

Re: monomorphism ...

1999-02-26 Thread Jerzy Karczmarczuk
John Hughes : > > Everybody agrees the monomorphism restriction is a pain: ... > So, let's make it visible, in the simplest possible way. Let there be TWO > forms of binding: x = e, and x := e (say). A binding of the form `x = e' is > interpreted using call-by-n

Re: Monomorphism

1999-02-25 Thread Fergus Henderson
On 24-Feb-1999, John C. Peterson <[EMAIL PROTECTED]> wrote: > You can't nuke monomorphism without addressing the ambiguity problem. If you've got the time, would you mind giving an example of the kind of ambiguity you're talking about? I think I know roughly the kind o

Re: Modifying the monomorphism restriction

1999-02-25 Thread Fergus Henderson
On 24-Feb-1999, Thomas Hallgren <[EMAIL PROTECTED]> wrote: > I agree with Johns objection to the compiler warning solution, so here is > another suggestion: > > The monomorphism restriction makes sure that certain values are computed > at most once by restricting them to be

Re: Modifying the monomorphism restriction

1999-02-25 Thread Fergus Henderson
On 24-Feb-1999, John Hughes <[EMAIL PROTECTED]> wrote: > > Everybody agrees the monomorphism restriction is a pain: [...] > On the other hand, interpreting such definitions using call-by-name when the > programmer expects call-by-need would REALLY introduce a trap for the

Re: Modifying the monomorphism restriction

1999-02-25 Thread Alex Ferguson
Joe English: > I was thinking of the example from the Haskell Report: > > let { len = genericLength xs } in (len, len) > > which, without the MR, computes 'len' twice. > Operationally I expect that in "let x = f y in ... x ... x", > 'f y' is only evaluated once, no matter what type it is.

Re: Modifying the monomorphism restriction

1999-02-24 Thread Alex Ferguson
Thomas Hallgren: > The monomorphism restriction makes sure that certain values are computed at most > once by restricting them to be used at only one type. Couldn't the same be > achieved by > > * getting rid the monomorphism restriction, i.e., let all definitions to be

Re: Modifying the monomorphism restriction

1999-02-24 Thread Thomas Hallgren
John Hughes wrote: > Some suggest that it is enough for compilers to issue a warning when using > call-by-name. I disagree strongly. I agree with Johns objection to the compiler warning solution, so here is another suggestion: The monomorphism restriction makes sure that certain valu

Re: Modifying the monomorphism restriction

1999-02-24 Thread Alex Ferguson
Joe English: > (Am I the only one who's never been bitten by the MR restriction?) If one always uses type sigs, or never/rarely uses compositional/ combinator style function definitions, it's much less likely to crop up. > How about leaving the 'a = b' binding form

Re: Modifying the monomorphism restriction

1999-02-24 Thread Christian Sievers
John Hughes wrote: > Everybody agrees the monomorphism restriction is a pain: Hmm well, it's really not a nice thing. > Some suggest that it is enough for compilers to issue a warning when using > call-by-name. I disagree strongly. Such a warning may alert the programmer >

Re: Modifying the monomorphism restriction

1999-02-24 Thread Alex Ferguson
n give the > answer, but in general, you would have to give a type unless `e' > already has a monotype. So you could use `x:=e' without a signature > exactly when you now could use `x=e' without one. That's the point, isn't it? > > * Monomorphism is deco

Monomorphism

1999-02-24 Thread John C. Peterson
You can't nuke monomorphism without addressing the ambiguity problem. At the very least, you need scoped type variables to disambiguate types in the absence of the MR. This ambiguity is a definite pitfall and the type errors resulting from this ambiguity will probably be even more puzzlin

Re: Modifying the monomorphism restriction

1999-02-24 Thread S. Alexander Jacobson
Why not allow the code-bloat and treat type information as a hint by which compilers/interpreters _may_ optimize? i.e. when an expresion like > foo=goo violates the monomorphism restriction allow overloading (and perhaps code bloat), but if foo is explicitly typed, > foo::Num a=> a

RE: Modifying the monomorphism restriction

1999-02-24 Thread R.S. Nikhil
> -Original Message- > From: Joe English [mailto:[EMAIL PROTECTED]] > Sent: Wednesday, February 24, 1999 2:36 PM > To: [EMAIL PROTECTED] > Subject: Re: Modifying the monomorphism restriction > > This is a good idea, except for the use of ':='. > I&#

Re: Modifying the monomorphism restriction

1999-02-24 Thread Joe English
I wrote: > Operationally I expect that in "let x = f y in ... x ... x", > 'f y' is only evaluated once, no matter what type it is. Which, of course, is not how Haskell actually works, if x :: (SomeClass a) => SomeType a. DOH! Please disregard my earlier remarks... --Joe English [EMAIL PR

Re: Modifying the monomorphism restriction

1999-02-24 Thread Joe English
Alex Ferguson <[EMAIL PROTECTED]> wrote: > Joe English: > > How about leaving the 'a = b' binding form as it is, > > (monomorphism restriction and all) and using 'a = ~ b' > > to indicate call-by-name. [...] > I like that much less [...] becaus

Modifying the monomorphism restriction

1999-02-24 Thread John Hughes
Everybody agrees the monomorphism restriction is a pain: * Often we WANT to make overloaded definitions of the form variable = expr * The eta-expansion fix is ugly, and only works if the variable has a function type * Adding a type signature instead is tedious during prototyping, and

Re: Modifying the monomorphism restriction

1999-02-24 Thread S.M.Kahrs
I just wanted to mention that John's idea of two different forms of binding, a polymorphic one with repeated evaluation and a monomorphic one with single evaluation, is not new. It is also in Xavier Leroy's PhD thesis "Polymorphic Typing of an Algorithmic Language", where he suggests two differen

Re: Modifying the monomorphism restriction

1999-02-24 Thread Joe English
John Hughes <[EMAIL PROTECTED]> wrote: > > Everybody agrees the monomorphism restriction is a pain: > [...] > So, let's make it visible, in the simplest possible way. Let there be TWO > forms of binding: x = e, and x := e (say). A binding of the form `x = e' is &

RE: Why change the monomorphism rules?

1998-12-21 Thread Mark P Jones
| Pro a change | Mark Jones mildly | Olaf Chitil?mildly [I can't locate his message] | | My rule of thumb is that the status quo wins if there's any | doubt, and there is, so I'll reverse my proposal and leave | things unchanged. Actually, I'm neither pro or agains

RE: Why change the monomorphism rules?

1998-12-21 Thread Simon Peyton-Jones
> Simon's latest report changes the relationship between monomorphism > and defaulting. This issue was never discussed at length by the > committee so I think I'll bring the discussion out here. John objected quite strongly to changing the way top-level monomorphism is res

Re: Why change the monomorphism rules?

1998-12-15 Thread Fergus Henderson
On 14-Dec-1998, John C. Peterson <[EMAIL PROTECTED]> wrote: > The old Hugs system implemented this new rule, rather by accident, > so I think we can say that this new rule has been thoroughly "tested". > My experience is that it is major pain in the ass, not an > improvement. By "The old Hugs s

RE: Why change the monomorphism rules?

1998-12-15 Thread Simon Peyton-Jones
> Simon's latest report changes the relationship between monomorphism > and defaulting. This issue was never discussed at length by the > committee so I think I'll bring the discussion out here. > ... > > Please take the time look into this issue and voice your opi

Re: Why change the monomorphism rules?

1998-12-14 Thread John C. Peterson
I can't speak for Hugs 1.3c, but Hugs 1.4 and prior systems use the proposed monomorphism rule, not the Haskell 1.4 rule. John

Why change the monomorphism rules?

1998-12-14 Thread John C. Peterson
Simon's latest report changes the relationship between monomorphism and defaulting. This issue was never discussed at length by the committee so I think I'll bring the discussion out here. In Haskell 1.4, top-level monomorphism could be resolved anywhere in the module. Thus, this is

monomorphism

1998-11-18 Thread David Feuer
Why is monomorphism necessary? The sections in the Report on this topic are very unclear (to me). The monomorphism restriction is particularly disturbing. I _really_ do not like the limitations on lambda. I am guessing that part of the problem may lie in trying to support polymorphism

Monomorphism wierdness

1998-11-18 Thread Simon Peyton-Jones
Folks: if you are into the fine detail of the monomorphism restriction then read on for a Haskell 98 wrinkle. It's a fine point, and I'm only circulating it because I don't want to make any un-announced changes to Haskell 98. Simon Mark [below] makes a good case, but I t

Re: monomorphism etc.

1998-11-13 Thread Fergus Henderson
On 12-Nov-1998, Lennart Augustsson <[EMAIL PROTECTED]> wrote: > > [...] if you dislike tuples you can use nested pairs At the cost of losing a little type-safety. -- Fergus Henderson <[EMAIL PROTECTED]> | "Binaries may die WWW: | but source code lives forever

Re: nested pairs (was Re: monomorphism etc.)

1998-11-12 Thread Claus Reinke
>PS. I've got a length function for ``heterogeneous lists'', as >they appear in nested pairs, in Hugs. However, it uses the >type system extensions available in 1.3c or in 1.4 [98 BETA]. >How much can you do in plain Haskell??? in Cayenne?-) oops. On second thought, this length

  1   2   >