[Haskell-cafe] The infamous evil monomorphism restriction (was: A bit of a shock - Memoizing functions)

2009-03-27 Thread Peter Verswyvelen
From a previous email in the beginners list I more or less understood that the monomorphism restriction will not exist anymore in Haskell Prime. Is this correct? On Fri, Mar 27, 2009 at 10:32 PM, Jonathan Cast jonathancc...@fastmail.fmwrote: On Fri, 2009-03-27 at 14:26 -0700, Kirk Martinez

[Haskell-cafe] Re: The infamous evil monomorphism restriction (was: A bit of a shock - Memoizing functions)

2009-03-27 Thread Peter Verswyvelen
, 2009 at 12:51 AM, Peter Verswyvelen bugf...@gmail.com wrote: From a previous email in the beginners list I more or less understood that the monomorphism restriction will not exist anymore in Haskell Prime. Is this correct? On Fri, Mar 27, 2009 at 10:32 PM, Jonathan Cast jonathancc...@fastmail.fm

Re: [Haskell-cafe] Is this related to monomorphism restriction?

2008-12-23 Thread wren ng thornton
- Integer) ) The alpha conversion, necessary before doing scope extension, is the step that might not have been apparent. Because @f@ is polymorphic in its argument, the different instances of @f@ can be polymorphic in different ways. This in turn is what leads to the ambiguity in @g@, monomorphism

Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-22 Thread Iavor Diatchki
On Sun, Dec 21, 2008 at 9:21 AM, Maurí­cio briqueabra...@yahoo.com wrote: Why isn't the last line of this code allowed? f :: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...) (...) The reason

[Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Maurí­cio
Why isn't the last line of this code allowed? f :: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...) (...) The reason is that a has type a :: (TestClass a, TestClass b) = (a,b) and then when we take

Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Ryan Ingram
You have a few options. In Haskell98 (no extensions): a () = (f,f) g () = fst (a ()) -- alternatively g x = fst (a ()) x Here you make it explicit that a and g are functions; the monomorphism restriction is there to stop things that look like values (and therefore you expect to only get

Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Iavor Diatchki
Hello, You can work around the monomorphism restriction with extensions but to fix the ambiguity in your program that Reiner pointed out you'll have to change the program to specify how you'd like to instantiate a. here are all the types once again: f :: (TestClass a) = a - Integer f = const 1

Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Luke Palmer
:: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (...) (...) The reason is that a has type a :: (TestClass a, TestClass b) = (a,b) and then when we take 'fst' of this value (as in g) we get g

[Haskell-cafe] Is this related to monomorphism restriction?

2008-12-20 Thread Maurí­cio
Hi, Why isn't the last line of this code allowed? f :: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (or even the third line would not be accepted). Is there something I could read to understand

Re: [Haskell-cafe] Is this related to monomorphism restriction?

2008-12-20 Thread Luke Palmer
On Sat, Dec 20, 2008 at 4:28 PM, Maurí­cio briqueabra...@yahoo.com wrote: Hi, Why isn't the last line of this code allowed? f :: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a Yep, monomorphism restriction. a, because it is syntactically not a function, must

Re: [Haskell-cafe] Is this related to monomorphism restriction?

2008-12-20 Thread Reiner Pope
On Sun, Dec 21, 2008 at 10:28 AM, Maurí­cio briqueabra...@yahoo.com wrote: Hi, Why isn't the last line of this code allowed? f :: (TestClass a) = a - Integer f = const 1 a = (f,f) g = fst a The only thing I can think about is monomorphism restriction, but it's allowed (or even the third

Re: [Haskell-cafe] monomorphism restriction

2008-06-16 Thread Ryan Ingram
questionable to me. Not necessarily, contrast these two definitions: f = foldr (+) 0 f_expensive = let n = head $ drop 10 $ fibs 1 1 in foldr (+) n With the monomorphism restriction in place, f_expensive only calculates n once. Without, it gets calculated each time f is instantiated. -- ryan

Re: [Haskell-cafe] monomorphism restriction

2008-06-14 Thread Rafal Kolanski
Ryan Ingram wrote: sumns 0 = 0 sumns x = sumns (x-1) + n Without the monomorphism restriction, computing n is a function call; it is evaluated each time it is asked for. I'm relatively new to Haskell, and since this topic already came up, I was wondering if anyone could explain to me how

Re: [Haskell-cafe] monomorphism restriction

2008-06-14 Thread Jonathan Cast
On Sat, 2008-06-14 at 17:19 +1000, Rafal Kolanski wrote: Ryan Ingram wrote: sumns 0 = 0 sumns x = sumns (x-1) + n Without the monomorphism restriction, computing n is a function call; it is evaluated each time it is asked for. I'm relatively new to Haskell, and since this topic

Re: [Haskell-cafe] monomorphism restriction

2008-06-13 Thread Ryan Ingram
On 6/11/08, Rex Page [EMAIL PROTECTED] wrote: Please remind me, again, of the advantages of f being something different from the formula defining it. fibs !a !b = a : fibs b (a+b) -- fibs :: Num a = a - a - [a] n = head $ drop 100 $ fibs 1 1 -- n :: Integer (due to monomorphism restriction

Re: [Haskell-cafe] monomorphism restriction

2008-06-13 Thread Jonathan Cast
On Wed, 2008-06-11 at 20:24 -0700, Don Stewart wrote: page: Definition of f: f = foldr (+) 0 Types: 0 :: (Num t) = t foldr (+) 0 :: Num a = [a] - a f :: [Integer] - Integer Please remind me, again, of the advantages of f being something different from the formula

[Haskell-cafe] monomorphism restriction

2008-06-11 Thread Rex Page
Definition of f: f = foldr (+) 0 Types: 0 :: (Num t) = t foldr (+) 0 :: Num a = [a] - a f :: [Integer] - Integer Please remind me, again, of the advantages of f being something different from the formula defining it. - Rex Page ___

Re: [Haskell-cafe] monomorphism restriction

2008-06-11 Thread Don Stewart
page: Definition of f: f = foldr (+) 0 Types: 0 :: (Num t) = t foldr (+) 0 :: Num a = [a] - a f :: [Integer] - Integer Please remind me, again, of the advantages of f being something different from the formula defining it. Overloaded 'constants' take a dictionary as an

patch applied (haskell-prime-status): Accepted: remove the monomorphism restriction

2008-05-14 Thread Simon Marlow
Wed May 14 08:12:34 PDT 2008 Simon Marlow [EMAIL PROTECTED] * Accepted: remove the monomorphism restriction M ./status.hs -1 +1 View patch online: http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514151234-12142-8883dd9b436af3208701e5dcd9b926e38391765c.gz

patch applied (haskell-prime-status): separate the various monomorphism restriction proposals

2008-05-14 Thread Simon Marlow
Wed May 14 08:12:12 PDT 2008 Simon Marlow [EMAIL PROTECTED] * separate the various monomorphism restriction proposals M ./status.hs -1 +17 View patch online: http://darcs.haskell.org/haskell-prime-status/_darcs/patches/20080514151212-12142-28aa86fa87208d58913b72b0fdb6be38e61e9a62.gz

RE: The monomorphism restriction and monomorphic pattern bindings

2008-05-01 Thread Simon Peyton-Jones
| Ok. So I counter-propose that we deal with pattern bindings like this: | |The static semantics of a pattern binding are given by the following |translation. A binding 'p = e' has the same meaning as the set of |bindings | | z = e | x1 = case z of { p - x1 } | ... |

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-30 Thread Ian Lynagh
On Wed, Apr 30, 2008 at 12:18:47PM +0100, Ross Paterson wrote: On Wed, Apr 23, 2008 at 10:32:24AM -0700, Simon Marlow wrote: The current proposal on the table for what to do about the monomorphism restriction (henceforth MR) is * remove the MR entirely Just to be clear, are we

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-28 Thread Iavor Diatchki
Hi, On Mon, Apr 28, 2008 at 9:42 AM, Simon Marlow [EMAIL PROTECTED] wrote: Ok. So I counter-propose that we deal with pattern bindings like this: The static semantics of a pattern binding are given by the following translation. A binding 'p = e' has the same meaning as the set of

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-28 Thread Ian Lynagh
On Mon, Apr 28, 2008 at 09:42:10AM -0700, Simon Marlow wrote: Ok. So I counter-propose that we deal with pattern bindings like this: The static semantics of a pattern binding are given by the following translation. A binding 'p = e' has the same meaning as the set of bindings

RE: The monomorphism restriction and monomorphic pattern bindings

2008-04-25 Thread Simon Peyton-Jones
| The report doesn't actually mention this translation although it is | widely used to implement pattern bindings, and in some compilers (not | GHC) the translation is done before type checking. | | What's interesting to me is that perhaps this gives us a way to | understand what the static

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-25 Thread Neil Mitchell
Hi Simon, Those additional reasons given are much more compelling, and should definately go on the wiki. I think the essential point is that it makes reasoning about the code simpler - regardless of the effect on implementation. My main remaining reservation is that: (x) /= x [EMAIL PROTECTED]

RE: The monomorphism restriction and monomorphic pattern bindings

2008-04-24 Thread Simon Peyton-Jones
| Iavor: | the change is valid. I do believe that you can probably work around | the problem in many situations but the question in my mind is why | should we have to work around stuff when we have a system that already | works? In other words, what problem do MBPs solve? ... | Neil: | Haskell

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-24 Thread Simon Marlow
, The current proposal on the table for what to do about the monomorphism restriction (henceforth MR) is * remove the MR entirely * adopt Monomorphic Pattern Bindings (MPB) Right now, the committee is almost uniformly in favour of dropping the MR, and most of us are coming round to the idea

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-23 Thread Iavor Diatchki
of (_,v) - v It seems that under MBP the second program is not equivalent to the first because it is more polymorphic. -Iavor On Wed, Apr 23, 2008 at 10:32 AM, Simon Marlow [EMAIL PROTECTED] wrote: Folks, The current proposal on the table for what to do about the monomorphism restriction

Re: The monomorphism restriction and monomorphic pattern bindings

2008-04-23 Thread Neil Mitchell
Hi * remove the MR entirely Finally! * adopt Monomorphic Pattern Bindings (MPB) There are 6 reasons on that page why we shouldn't adopt MPB - of those number 5 I think is particularly compelling. There seems to be 1 main reason to remove it, which is that it has a complex translation to

is -fno-monomorphism-restriction evil?

2007-10-09 Thread Jorge Marques Pelizzoni
Hi, all! It may be a side-effect of being a newbie, but many times I find the -fno-monomorphism-restriction quite handy. Is it intrinsically evil? I mean, has anyone had a bad time using it or does it imply some runtime performance overhead? I guess it is not portable, is it? Thanks in advance

Re: is -fno-monomorphism-restriction evil?

2007-10-09 Thread Matthew Danish
On Tue, Oct 09, 2007 at 03:29:55PM -0300, Jorge Marques Pelizzoni wrote: It may be a side-effect of being a newbie, but many times I find the -fno-monomorphism-restriction quite handy. Is it intrinsically evil? I mean, has anyone had a bad time using it or does it imply some runtime

monomorphism restriction confusions

2007-07-09 Thread Isaac Dupree
Haskell98's monomorphism restriction is too confusing! See my mistaken GHC bug report http://hackage.haskell.org/trac/ghc/ticket/1503. Whether a binding is monomorphic depends not just on syntax, but on the amount of type constraints on the right-hand side of a binding - and I didn't realize

Re: [GHC] #1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together

2007-07-03 Thread GHC
#1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together --+- Reporter: [EMAIL PROTECTED] |Owner: Type: bug| Status: reopened

Re: [GHC] #1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together

2007-07-03 Thread GHC
#1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together --+- Reporter: [EMAIL PROTECTED] |Owner: Type: bug| Status: closed

Re: [GHC] #1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together

2007-07-02 Thread GHC
#1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together --+- Reporter: [EMAIL PROTECTED] |Owner: Type: bug| Status: closed

[GHC] #1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together

2007-07-02 Thread GHC
#1485: -fno-monomorphism-restriction -fallow-undecidable-instances do not play nicely together +--- Reporter: [EMAIL PROTECTED] | Owner: Type: bug| Status: new

Re: [GHC] #1398: -fno-monomorphism-restriction suggested when not appropriate

2007-06-06 Thread GHC
#1398: -fno-monomorphism-restriction suggested when not appropriate --+- Reporter: [EMAIL PROTECTED] |Owner: Type: feature request| Status: closed Priority: normal

Re: [GHC] #1398: -fno-monomorphism-restriction suggested when not appropriate

2007-06-06 Thread GHC
#1398: -fno-monomorphism-restriction suggested when not appropriate --+- Reporter: [EMAIL PROTECTED] |Owner: Type: feature request| Status: closed Priority: normal

Re: [GHC] #1398: -fno-monomorphism-restriction suggested when not appropriate

2007-06-06 Thread GHC
#1398: -fno-monomorphism-restriction suggested when not appropriate --+- Reporter: [EMAIL PROTECTED] |Owner: Type: feature request| Status: closed Priority: normal

[GHC] #1398: -fno-monomorphism-restriction suggested when not appropriate

2007-05-31 Thread GHC
#1398: -fno-monomorphism-restriction suggested when not appropriate +--- Reporter: [EMAIL PROTECTED] | Owner: Type: feature request| Status: new Priority: normal

Re: [GHC] #1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction

2007-04-30 Thread GHC
#1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction -+-- Reporter: guest |Owner: Type: bug | Status: closed Priority: normal|Milestone

Re: [GHC] #1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction

2007-04-29 Thread GHC
#1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction -+-- Reporter: guest |Owner: Type: bug | Status: closed Priority: normal|Milestone

Re: [GHC] #1296: -fwarn-monomorphism-restriction breaks package compilation

2007-04-27 Thread GHC
#1296: -fwarn-monomorphism-restriction breaks package compilation -+-- Reporter: guest |Owner: Type: bug | Status: closed Priority: normal|Milestone

[GHC] #1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction

2007-04-26 Thread GHC
#1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction ---+ Reporter: guest | Owner: Type: bug | Status: new Priority: normal| Milestone

Re: [GHC] #1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction

2007-04-26 Thread GHC
#1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction -+-- Reporter: guest |Owner: Type: bug | Status: closed Priority: normal|Milestone

[GHC] #1296: -fwarn-monomorphism-restriction breaks package compilation

2007-04-26 Thread GHC
#1296: -fwarn-monomorphism-restriction breaks package compilation ---+ Reporter: guest | Owner: Type: bug | Status: new Priority: normal| Milestone

Re: [Haskell-cafe] Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
Neil Mitchell wrote: http://haskell.org/hawiki/MonomorphismRestriction Note to others (esp Cale): does this page not appear on the new wiki? I did a very rough quick conversion: http://www.haskell.org/haskellwiki/MonomorphismRestriction The old wiki is locked, for obvious reasons. But

[Haskell-cafe] Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Bayley, Alistair
Neil Mitchell wrote: http://haskell.org/hawiki/MonomorphismRestriction Note to others (esp Cale): does this page not appear on the new wiki? I did a very rough quick conversion: http://www.haskell.org/haskellwiki/MonomorphismRestriction The old wiki is locked, for obvious reasons.

[Haskell-cafe] Re: Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Yitzchak Gale
I wrote: I did a very rough quick conversion: http://haskell.org/hawiki/MonomorphismRestriction http://www.haskell.org/haskellwiki/MonomorphismRestriction Oops. Moved to: http://www.haskell.org/haskellwiki/Monomorphism_Restriction Alistair Bayley wrote: You can see the source for the page

[Haskell-cafe] RE: Old wiki page source text - was Monomorphism restriction

2007-01-25 Thread Bayley, Alistair
I wrote: I did a very rough quick conversion: http://haskell.org/hawiki/MonomorphismRestriction http://www.haskell.org/haskellwiki/MonomorphismRestriction Oops. Moved to: http://www.haskell.org/haskellwiki/Monomorphism_Restriction Alistair Bayley wrote: You can see the source for

[Haskell-cafe] Monomorphism restriction

2007-01-23 Thread Marco Túlio Gontijo e Silva
Hello, I talked for a while with bd_ about this on #haskell, and I think maybe I'm just being silly. But I can't get why: lambda = \x - length (show x) or dot = length . show is different from pre x = length $ show x I read about monomorphism restriction on the haskell 98 report, but I

Re: [GHC] #1090: Bad monomorphism-restriction-related type error message

2007-01-09 Thread GHC
#1090: Bad monomorphism-restriction-related type error message -+-- Reporter: kirsten | Owner: Type: bug | Status: closed Priority: lowest

[GHC] #1090: Bad monomorphism-restriction-related type error message

2007-01-07 Thread GHC
#1090: Bad monomorphism-restriction-related type error message +--- Reporter: kirsten | Owner: Type: bug | Status: new Priority: lowest

Re: Monomorphism restriction

2006-10-14 Thread Iavor Diatchki
Hello, On 10/14/06, Bulat Ziganshin [EMAIL PROTECTED] wrote: Hello haskell-prime, first is the monomorphism restriction. why isn't it possible to check _kind_ of parameter-less equation and apply monomorphism restrictions only to values of kind '*'? so, this: sum = foldr1 (*) will become

Re: Monomorphism restriction - is this still needed for efficiency?

2006-06-12 Thread Simon Marlow
Brian Hulley wrote: I'm wondering if the monomorphism restriction is now just an anachronism from Haskell 98 or if it is still needed for efficiency ie should I just now use -fno-monomorphism-restriction when compiling all my code to consign it to the dustbin of history? :-) A related

Re: Monomorphism restriction - is this still needed for efficiency?

2006-06-12 Thread Brian Hulley
Simon Marlow wrote: Brian Hulley wrote: I'm wondering if the monomorphism restriction is now just an anachronism from Haskell 98 or if it is still needed for efficiency ie should I just now use -fno-monomorphism-restriction when compiling all my code to consign it to the dustbin of history

Monomorphism restriction - is this still needed for efficiency?

2006-06-09 Thread Brian Hulley
Hi - I'm wondering if the monomorphism restriction is now just an anachronism from Haskell 98 or if it is still needed for efficiency ie should I just now use -fno-monomorphism-restriction when compiling all my code to consign it to the dustbin of history? :-) A related question

[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 AGC.lhs

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

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

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

2006-02-27 Thread Eike Scholz
expression. Consider that I have disabled the monomorphism restriction in module AGC.lhs (which is attached). and I have a toplevel definition of: mylength = synAttr listLength loding the module in ghci (6.4) gives (beside some correct warnings): $ Ok, modules loaded: Main. $ *Main :type

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

2006-02-27 Thread Ben Rudiak-Gould
Eike Scholz wrote: mylength = synAttr listLength $ *Main :type synAttr $ synAttr :: (Data b) = ((?stack::[Dyn]) = b - a) - Attr a $ *Main :type listLength $ listLength :: (?stack::[Dyn]) = List - Float $ *Main :type (synAttr listLength) $ (synAttr listLength) :: Attr Float $ *Main :type

RE: -fno-monomorphism-restriction

2004-12-03 Thread Simon Peyton-Jones
| b) this is a feature request: you want a flag -fmonomorphism-restriction | to restore the monomorphism restriction even if it's been turned | off by an earlier flag? I've implemented this flag in the HEAD, as you requested. It'll be in 6.4 Simon

RE: -fno-monomorphism-restriction

2004-11-30 Thread Simon Peyton-Jones
- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Christian Maeder | Sent: 29 November 2004 16:31 | To: Simon Peyton-Jones | Cc: GHC Users Mailing List | Subject: Re: -fno-monomorphism-restriction | | I've found a much shorter example (without imports

Re: -fno-monomorphism-restriction

2004-11-29 Thread Christian Maeder
OPTIONS line, will make it go through) Cheers Christian {-# OPTIONS -fno-monomorphism-restriction #-} module NoMonoRestr where data ShATerm = ShAAppl String [Int] [Int] data ATermTable = ATermTable getATerm :: ATermTable - ShATerm getATerm = undefined data Annotation = Annotation data Annoted

Re: -fno-monomorphism-restriction

2004-11-29 Thread Christian Maeder
Christian Maeder wrote: I've found a much shorter example (without imports) that does not compile. and shorter: {-# OPTIONS -fno-monomorphism-restriction #-} module NoMonoRestr where data ATermTable = ATermTable data Annotation = Annotation data Annoted a = Annoted a [Annotation] toPair

RE: -fno-monomorphism-restriction

2004-11-26 Thread Simon Peyton-Jones
I'm not sure whether you are saying (a) or (b): a) This is a compiler bug; even with -fno-monomorphism-restriction the module should compile. Are you sure? b) this is a feature request: you want a flag -fmonomorphism-restriction to restore the monomorphism restriction even

Re: -fno-monomorphism-restriction

2004-11-26 Thread Christian Maeder
Simon Peyton-Jones wrote: I'm not sure whether you are saying (a) or (b): a) This is a compiler bug; even with -fno-monomorphism-restriction the module should compile. Are you sure? b) this is a feature request: you want a flag -fmonomorphism-restriction to restore

Re: -fno-monomorphism-restriction

2004-11-26 Thread Christian Maeder
I wrote | If someone wants to reproduce the error, do the following: | 1) check out HetCATS repository with: | cvs -d pserver:[EMAIL PROTECTED]:/repository co | HetCATS | 2) comment out variable HC_PACKAGE in the Makefile (to avoid dependency | from uni) | 3) add the flag -fno-monomorphism

-fno-monomorphism-restriction

2004-11-24 Thread Christian Maeder
Hi, I've a file ATC/Sml_cats.hs that does not compile (see below) with the flag -fno-monomorphism-restriction (ghc 6.2.2), whereas it compiles fine without that option. Since I want to use -fno-monomorphism-restriction for other files (from programatica) I've a problem, because

Re: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
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 validity of the monomorphism restriction

RE: Solution to the monomorphism restriction/implicit parameter problem

2003-08-14 Thread Ben Rudiak-Gould
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 over the ?y parameter, to get z :: (?y::Int) = Int, No, it's not necessary that z

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 in

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

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 hand, the following does work

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 implicit

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.5 of the Haskell 98 language report

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 [EMAIL PROTECTED] http

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 unwary. Some suggest

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. If

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 used at only one type

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 at the time

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

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 interpreted using call-by-name, and may

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 as it is, (monomorphism

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 values

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 overloaded

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'd hate to lose that symbol from the programmers

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

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 [...] because I consider it (still) to be the wrong 'default

the monomorphism restriction (was: instance contexts)

1998-07-17 Thread Fergus Henderson
On 15-Jul-1998, Alex Ferguson [EMAIL PROTECTED] wrote: Fergus Henderson writes of: the monomorphism restriction (which exists for a similar reason, to ensure termination of type inference). Is this true? The rationale normally given for it by its advocates (boo, hiss) seems invariably