RE: Garbage collecting CAFs

2005-09-23 Thread Simon Peyton-Jones
A quick reply before running to ICFP The trouble with CAFs is this ints :: [Int] ints = [1,2..] f a b = ...ints... The 'ints' CAF is alive at any point in program execution at which 'f' can be called in the future. But a call to 'f' may be represented only by a reference to f's entry point

RE: FFI: calling Haskell from C++?

2005-09-14 Thread Simon Peyton-Jones
There’s been a bit of traffic about calling Haskell from C++ recently, and I know that calling C++ from Haskell is a frequently asked question. (E.g. Koen Claessen was asking me about it this week.)  It also seems to be somewhat platform dependent.  (Esp on Windows, I think.)    

RE: Profiling under 6.4.1 and Solaris segfaults

2005-09-02 Thread Simon Peyton-Jones
Does this happen on anything other than Solaris? We don't have local access to Solaris hardware at the moment. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Nils Anders Danielsson | Sent: 29 August 2005 18:04 | To: gl

RE: C--

2005-08-17 Thread Simon Peyton-Jones
| I am trying to understand the role of cmm files in the current GHC | compiler build process (I am guessing, they have replaced .hc files | like PrimOps and AutoApply). Yes, that's exactly right. | They are compiled by the stage1 compiler. Is ability to compile cmm | preserved in the compiler fi

RE: Functional Dependencies

2005-08-17 Thread Simon Peyton-Jones
| > class C a b | a -> b | > instance C Int Bool | > | > f :: forall a. C Int a => a -> a | > f x = x | > | > GHC rejects the type signature for f, because we can see that 'a' *must | > be* Bool, so it's a bit misleading to universally quantify it. | | Ok, maybe this is a reasonabl

RE: Functional Dependencies

2005-08-11 Thread Simon Peyton-Jones
You raise a vexed question, which has been discussed a lot. Should this typecheck? class C a b | a -> b instance C Int Bool f :: forall a. C Int a => a -> a f x = x GHC rejects the type signature for f, because we can see that 'a' *must be* Bool, so it's a bit m

RE: Re[4]: C--

2005-08-09 Thread Simon Peyton-Jones
| so, C-- will never be compiled faster than asm, and, at this moment, | cannot give a better optimization than C? as a result, it's use will have no | meaning until qc-- compiler will advance in it's optimization? For those people interested only in getting their Haskell programs compiled, that'

RE: Re[2]: C--

2005-08-09 Thread Simon Peyton-Jones
| SPJ> Actually using C-- itself as an output medium keeps slipping down the | SPJ> agenda, mainly because no one asks for it! | | because you don't advertise it! :) if you will advertise the | following, preferably with less or more concrete numbers, then we will | know whether we want it or no

RE: C--

2005-08-08 Thread Simon Peyton-Jones
We're already compiling via an intermediate data type that is closely based on C--. That internal data type is used regardless of whether you emit C, asm, or C--. Actually using C-- itself as an output medium keeps slipping down the agenda, mainly because no one asks for it! But I still fully i

RE: Inductive kinds

2005-08-08 Thread Simon Peyton-Jones
You mean something like 'datakind' in Tim Sheard's Omega? Nothing is imminent. What I'd like to do, though, is to use data *types* at the type level, rather than reproduce the data-type declaration stuff at the kind level. Thus data Nat = S Nat | Z data Foo :: Nat -> * where

RE: Inferred type is less polymorphic than expected?

2005-08-08 Thread Simon Peyton-Jones
| > Are you saying, that the second error causes the first one? Thus, | > everything is caused by 'printer' being recursively defined? | Yes, that's what I believe. I'm not sure why it shows the first error | message at all; in my experience, strange things happen when ghc | continues after an erro

RE: Lambda Lifting and Haskell

2005-07-25 Thread Simon Peyton-Jones
You're not asking a question about Haskell, but about Haskell implementations, and they may make different choices. GHC, for example, does not do lambda lifting. See http://research.microsoft.com/copyright/accept.asp?path=/users/simonpj/p apers/spineless-tagless-gmachine.ps.gz&pub=34 for a summ

RE: Contexts differ in length

2005-07-22 Thread Simon Peyton-Jones
skell-users@haskell.org; Simon Peyton-Jones | Subject: Contexts differ in length | | Hi all, | | A while ago I sent an email to the glasgow haskell users maillinglist to | explain how the "Contexts differ in length" feature (or bug :-)) | restricted me in writing a haskell applicatio

RE: GADTs and pedagogy was Re: GADTs and fundeps

2005-07-21 Thread Simon Peyton-Jones
| > You mean, if the data type being defined doesn't actually use the | > generality of GADTs, allow GADT syntax, and deriving() too? | | Yes, that would be very nice for the HaskellDemo and new users. | I'd definitely switch all of my non-GADT datatypes to use that. I finally got around to doing

RE: option for enabling generalized deriving for newtypes

2005-07-11 Thread Simon Peyton-Jones
Not at the moment. There could be -- it's just one more thing to implement and document, but it's a relatively easy one. Does anyone else have an opinion? Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Wolfgang Jeltsc

RE: resolving Show instance

2005-06-30 Thread Simon Peyton-Jones
path gets the inferred type path :: forall a. [a] This polymorphic type is instantiated once when it is passed to 'subterm' and again, quite separately, when it is passed to 'shows'. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROT

Documentation for GHC primops

2005-06-29 Thread Simon Peyton-Jones
Dear GHC users This message is a request for help with a well-contained task that will improve GHC's Haddock documentation. GHC provides lots of primitive operations. They are described in a single ASCII files primpos.txt.pp; the description in that file gives types and English-language descript

RE: ANNOUNCE: GHC survey results

2005-06-29 Thread Simon Peyton-Jones
| That's fair. I just hope the implicit parameter implementation is | orthogonal enough that it's worth keeping around. It's only *linear* implicit parameters (always regarded as highly experimental) that we might nuke, not implicit parameters themselves. Does anyone out there actually find lin

RE: Bignums in Haskell

2005-06-22 Thread Simon Peyton-Jones
There's nothing inherently imperative about bignums. The current algorithms may have an imperative flavour, but that may be partly because that's what suits the implementation language. If the algorithms are divide-and-conquer, perhaps a tree representation would work very nicely. And even in th

RE: Bignums in Haskell

2005-06-21 Thread Simon Peyton-Jones
| >> Do any of you have insight into why GHC uses GMP as opposed to | >> another library for arbitrary precision numbers? | > ... | | Right - that's three reasons to use it. Some reasons *not* to use it | are: it has an awkward license, it's big, it needs updating, and we run | into problems whe

RE: GHC hang

2005-06-07 Thread Simon Peyton-Jones
irectly. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of John Goerzen | Sent: 06 June 2005 21:21 | To: glasgow-haskell-users@haskell.org | Subject: Re: GHC hang | | On 2005-06-06, Simon Peyton-Jones <[EMAIL PROTECTED]> wrot

RE: Simplifier output explanation needed

2005-06-07 Thread Simon Peyton-Jones
Yes $s is for specialised versions of (usually overloaded) functions. If you are using -02 you can also get specialised versions from so-called constructor specialisation, when the function is specialised for a particular argument pattern. I don't know why the strictness annotations disappear, but

RE: [Haskell] Template Haskell Question: Spliced expr. of type TypeQ

2005-06-07 Thread Simon Peyton-Jones
[Redirecting to GHC users] I'm afraid I never got around to implementing splices in types, I'm afraid. Interestingly, you are the first person who's asked for them. I forget the details... it's not a massive job to implement them, but not trivial either. If this is important for other people too

RE: GHC hang

2005-06-06 Thread Simon Peyton-Jones
Lots of people seem to have had problems compiling Wash with GHC 6.4. As far as we know, they are all caused by the fact that the package-configuration file format changed in 6.4, and you need to fix that before it'll compile cleanly. Maybe someone can make available a version of Wash that works,

RE: Contexts differ in length

2005-05-27 Thread Simon Peyton-Jones
| A while ago I sent an email to the glasgow haskell users maillinglist to | explain how the "Contexts differ in length" feature (or bug :-)) | restricted me in writing a haskell application. I was hoping for a | reply, however I didn't receive one (yet). It's a sensible suggestion. Until now no

RE: deprecate a constructor?

2005-05-05 Thread Simon Peyton-Jones
skell-users- | [EMAIL PROTECTED] On Behalf Of Simon Peyton-Jones | Sent: 15 April 2005 14:58 | To: Johannes Waldmann; glasgow-haskell-users@haskell.org | Subject: RE: deprecate a constructor? | | Apparently not at the moment but it should be. | | As in a 'hiding' list, deprecating "T&

RE: Partial application of type constructors?

2005-04-19 Thread Simon Peyton-Jones
Allowing partially applied type synonyms amounts to allowing lambda at the type level, and that requires higher-order unification, and loses principal types (I think). So as of today, they are definitely out. If you look at the paper about "boxy types" on my home page, you'll see ways of extendin

RE: hi-boot and dependencies bug?

2005-04-16 Thread Simon Peyton-Jones
6.4 does mutual recursion much much better. See the manual. Don't expend much effort on mutual recn in 6.2 S | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Isaac Jones | Sent: 16 April 2005 01:46 | To: GHC-users list | Cc:

Do you use GHC?

2005-04-15 Thread Simon Peyton-Jones
Dear Haskell folk, PLEASE READ THIS IF YOU USE THE Glasgow Haskell Compiler (GHC). I virtually never send messages to overlapping sets of lists, but I'm doing so this time, because I'd really like to get to everyone who uses GHC. Here at GHC HQ, we are often asked how many people use GHC, and w

RE: Re[2]: GHC 6.4/mingw32: files larger than 4 GBandhFileSize/hSetFileSize/c_stat

2005-04-15 Thread Simon Peyton-Jones
I have no clue what the right thing here is. Simon M is away today and Monday, but he'll doubtless tell you on Tuesday. He is supreme being for this kind of stuff. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Bulat

RE: deprecate a constructor?

2005-04-15 Thread Simon Peyton-Jones
Apparently not at the moment but it should be. As in a 'hiding' list, deprecating "T" would deprecate the *type* T and the *data constructor* T. There'd be no way to deprecate one without the other, except by giving them different names. (That's a bit of a shortcoming in hiding lists already, so

RE: GADTs and pedagogy was Re: GADTs and fundeps

2005-04-08 Thread Simon Peyton-Jones
| I doubt pedagogics was an important part of your goal with GADTs, but now | several people wish that "deriving Show" worked so that GADTs could be used for | everything. You mean, if the data type being defined doesn't actually use the generality of GADTs, allow GADT syntax, and deriving() too?

RE: GADTs and fundeps

2005-04-08 Thread Simon Peyton-Jones
Bjorn You are quite right. Indeed GADTs don't interact properly with type classes at all, let alone functional dependencies, I'm afraid. I decided to pause and release before attending to this; it's not trivial to do it right. One merit of pausing is that I can collect examples that people act

RE: Functional dependencies, principal types, and decidable typechecking

2005-04-05 Thread Simon Peyton-Jones
Manuel Your short program tickles a lot of different questions. Here's an explanation. Simon | Assume the following type class declarations with functional | dependencies: Actually much of the behaviour you see happens without fundeps. | > {-# OPTIONS -fglasgow-exts #-} | > | > class C a b c

RE: Rebindable syntax for monads and arrows

2005-04-04 Thread Simon Peyton-Jones
notation. Which is, I hope, enough for you. Simon | -Original Message- | From: Amr A Sabry [mailto:[EMAIL PROTECTED] | Sent: 24 January 2005 19:40 | To: Simon Peyton-Jones | Cc: Amr A Sabry; [EMAIL PROTECTED] | Subject: Re: Rebindable syntax for monads and arrows | | > You've conv

RE: [Haskell] GHC: Setting default +RTS options at compile time?

2005-03-18 Thread Simon Peyton-Jones
[Redirecting to GHC users, which is the right place for GHC related questions.] | Is there any way to specify at compile/link time default options for GHC | program +RTS options? No. This is a long-standing feature request. It makes perfect sense, but needs someone to design and implement it.

RE: [Haskell] Using -main-is with GHC 6.4/Windows

2005-03-18 Thread Simon Peyton-Jones
[Redirecting to GHC users, which is where GHC-specific questions belong] | OK, it's not so bad. If I delete the AffyDataCalc.o file before compiling | AffyDataCalcTest, it all works fine. ... | Hmmm... is there something the GHC --make feature can do to force | recompilation of the other modules

RE: ANNOUNCE: GHC version 6.4

2005-03-14 Thread Simon Peyton-Jones
| = | > The (Interactive) Glasgow Haskell Compiler -- version 6.4 | > | = | 2. What's up with "Warning: orphan instances"? I believe I forgot do document the -fwarn-orphans

RE: Restricted Types and Infinite Loops

2005-03-10 Thread Simon Peyton-Jones
TED] | Sent: 18 February 2005 09:36 | To: Ralf Laemmel | Cc: GHC Users; Simon Peyton-Jones | Subject: Re: Restricted Types and Infinite Loops | | On Fri, 2005-02-18 at 02:18 +0100, Ralf Laemmel wrote: | | > Here I assume that you don't _really_ depend on ClassB to be a | > superclass

RE: infix type operators

2005-03-09 Thread Simon Peyton-Jones
OK, it's done for 6.4 SImon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Ross Paterson | Sent: 08 March 2005 16:29 | To: glasgow-haskell-users@haskell.org | Subject: infix type operators | | The User's Guide says: | |

RE: infix type operators

2005-03-09 Thread Simon Peyton-Jones
Yes, that makes sense. I think I will do that. Whether it'll make it into 6.4 is doubtful S | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Ross Paterson | Sent: 08 March 2005 16:29 | To: glasgow-haskell-users@haskell.org |

RE: [Haskell] "Classic" vs. "Cunning Newtype" Derivation

2005-03-08 Thread Simon Peyton-Jones
[redirecting to GHC users list] John is right. I've added something to the user manual to say so. | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of John Meacham | Sent: 08 March 2005 00:20 | To: haskell@haskell.org | Subject: Re: [Haskell] "Classic" vs

RE: GHC 6.4 release candidates available

2005-03-07 Thread Simon Peyton-Jones
| >If you could specify overlapping on a per-instance basis, then that | >would be a way around the problem. Yes, that's the solution I prefer. The only question is when to action it | This worked in all GHCi before 6.4 - so something has broken the (in mu | opinion) correct | behavior. Was

RE: gunfoldl

2005-03-03 Thread Simon Peyton-Jones
This crash is fixed, in the HEAD and 6.4. It turned out to be a desugaring bug involving existentials etc. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Akos Korosmezey | Sent: 18 February 2005 20:05 | To: GHC-users l

RE: GHC 6.4 release candidates available

2005-03-03 Thread Simon Peyton-Jones
PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Keean Schupke | Sent: 02 March 2005 18:33 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users@haskell.org | Subject: Re: GHC 6.4 release candidates available | | Erm, what is the module context of GHCi? I thought ghci | used the cont

RE: GHC 6.4 release candidates available

2005-03-02 Thread Simon Peyton-Jones
o travelled with the instance decl, but it doesn't (yet). A good feature request. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Keean Schupke | Sent: 02 March 2005 17:20 | To: Simon Peyton-Jones | Cc: glasgow-

RE: GHC 6.4 release candidates available

2005-03-02 Thread Simon Peyton-Jones
Ralf You have a pragma "-fallow-overlapping-instances" in Test.hs, and indeed it is honoured when compiling Test.hs. But it's not taken into account when compiling top-level expressions, or, indeed, if you were to import Test into another module. If you say ":set -falllow-overlapping-instances"

RE: gunfoldl

2005-02-28 Thread Simon Peyton-Jones
Regardless of the programming, this should not have crashed GHC. I've fixed it, and added a regression test. Thanks for bringing it up. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Akos Korosmezey | Sent: 18 Februa

RE: gunfoldl

2005-02-25 Thread Simon Peyton-Jones
There's a real bug in the desugarer here, quite apart from the programming question. I'll look into it Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Akos Korosmezey | Sent: 18 February 2005 20:05 | To: GHC-users list

RE: Kinds in ghc

2005-02-25 Thread Simon Peyton-Jones
Well, it's a bug really, but not one that's easy to fix. Thanks for pointing it out; I've added it as a SourceForge bug so we don't forget it. SImon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Johan Glimming | Sent: 24 Fe

RE: Infix typeconstructors shown as prefix

2005-02-25 Thread Simon Peyton-Jones
Ive fixed this to print the parens round the type constructor anyway. But it won't print infix. Doing the right thing requires knowledge of fixities, which isn't (yet) plumbed to the right place S | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROT

RE: GHC-problem with parsing infix type synonyms - bug?

2005-02-23 Thread Simon Peyton-Jones
OK, done. I've documented infix classes too. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Johan Glimming | Sent: 17 February 2005 10:04 | To: ; Simon Marlow | Subject: Re: GHC-problem with parsing infix type synonym

RE: Restricted Types and Infinite Loops

2005-02-11 Thread Simon Peyton-Jones
Simon You've found an interesting case. First, you are skating on thin ice here. GHC's ability to build recursive dictionaries is quite experimental, and you are relying on it completely. But you're right: it "should" work. I can see why it isn't but I have not got it clear enough in my hea

RE: Unboxed Tuples

2005-02-07 Thread Simon Peyton-Jones
f x = let (p,q) = case h x of (# p,q #) -> (p,q) in (q,p) Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Adrian Hey | Sent: 07 February 2005 13:03 | To: Simon Peyton-Jones; glasgow-haskell-user

RE: STM check/MonadPlus

2005-02-07 Thread Simon Peyton-Jones
Thanks for the typo. Yes, for Haskell guys 'guard' is fine; but the main audience for the paper is non-haskell folk, so we have to spell out the defn. S | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Remi Turk | Sent: 06 Feb

RE: Unboxed Tuples

2005-02-07 Thread Simon Peyton-Jones
Good point. Yes you can rely on it; but the binding is lazy. So for this h :: Int -> (# String, String #) h = ... f x = let (# p,q #) = h x in ... you'll get f x = let (p,q) = case h x of (# p,q #) -> (p,q) in ... So the call to h only happens

RE: recursive group context bug?

2005-01-28 Thread Simon Peyton-Jones
The Report says that the functions of a mutually recursive group must all have the same context. It's a bit of a funny rule, and it's more restrictive than absolutely necessary, but that's what Haskell says. I could work to lift the restriction in GHC, but it only seems to come up in toy programs

RE: self-import

2005-01-19 Thread Simon Peyton-Jones
ginal Message- | From: Thomas Hallgren [mailto:[EMAIL PROTECTED] | Sent: 18 January 2005 22:12 | To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org | Cc: [EMAIL PROTECTED] | Subject: Re: self-import | | Simon Peyton-Jones wrote: | | >I quite liked this idea until I thought of this: | >

RE: self-import

2005-01-18 Thread Simon Peyton-Jones
| And if it turns out we are in the mood to look at extending the | inport/export/module syntax perhaps we could also consider the qualified | export idea posted a few weeks ago. | | That was so that you could say: | | import Graphics.UI.Gtk | | and then use Button.setText (rather than buttonSet

RE: self-import

2005-01-18 Thread Simon Peyton-Jones
| It would be useful to be able to do a | | module Doc.Pretty.Long.Name where | | import Doc.Pretty.Long.Name as This | | so within the module we can refer to itself as 'This' without having to | write out the full name, however ghc complains that the hi file for the | module it is trying to co

RE: 6.4 News

2005-01-06 Thread Simon Peyton-Jones
| I was curious whether type assosiated classes will make it into 6.4? I | think it would be a very useful thing. | | http://research.microsoft.com/Users/simonpj/papers/assoc-types/index.htm Definitely not, I'm afraid. Implementation isn't started. It's far from straightforward, which is why I'

RE: [Haskell-cafe] GHC for .NET?

2005-01-05 Thread Simon Peyton-Jones
| Understandably, however, there is real resistance in language communities like Haskell's to changing | or even extending a language for the sake of interoperability and API access: instead people work | incredibly hard to encode interoperability via existing mechanisms. In the end, whoever picks

RE: [Haskell-cafe] GHC for .NET?

2005-01-04 Thread Simon Peyton-Jones
| "The GHC compiler for .NET is currently under development at | Microsoft Research, Cambridge". | | Hmm. That location sounds familiar :-) Does anyone know if this is | actually going to happen? Or if there's any code anywhere, however | experimental, to try? It'd make a lot of sense to g

RE: CVS HEAD ghc fails with "Panic!"

2004-12-21 Thread Simon Peyton-Jones
I reckon I've fixed this, at last. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Peter Simons | Sent: 20 October 2004 17:10 | To: [EMAIL PROTECTED] | Subject: CVS HEAD ghc fails with "Panic!" | | Hi, | | the GHC vers

RE: Scoped type variables

2004-12-20 Thread Simon Peyton-Jones
| Some design choices are unclear, at least to me. First, the | separation of body and signature. I am used to locally introduced | identifiers being visible locally too (i.e. requiring minimal | scrolling through a file). This would break, meaning that I have to | know which identifier was used in

RE: Error building GHC: can't locate import `Package'

2004-12-20 Thread Simon Peyton-Jones
I think it's just that you have an old file ParsePkgConfLite.hs in your directory. The make system finds it and tries to compile it. Easiest fix: remove the whole of ghc/utils/ghc-pkg, and do cvs update. S | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [E

RE: Scoped type variables

2004-12-20 Thread Simon Peyton-Jones
| Would it help to stick the quantifier at the beginning of | the type declaration? | | > forall a b . g :: Foo a b => [a] -> [a] | > g = ... Since GHC already allows explicit quantifiers, I had indeed wondered about saying that a type sig only brings type variables into scope if it has a

Scoped type variables

2004-12-17 Thread Simon Peyton-Jones
OK, OK, I yield! This message is about lexically scoped type variables. I've gradually become convinced that if you write f :: [a] -> [a] f x = then the type variable 'a' should be in scope in . At present in GHC you have to write f (x :: [a]) = to bring 'a' into sco

RE: -ddump-parsed and infix operators

2004-12-15 Thread Simon Peyton-Jones
You're right: they are passed left-associatively, and fixed up later. That way the parser does not need to know about associativity and precedence. So it's not a bug. Just something you need to know about -ddump-parsed! Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgo

RE: A question about the "awkward squad"

2004-12-06 Thread Simon Peyton-Jones
| > and is it (still?) true that GHC never expands them? | | I'm not sure if GHC guarantees never to duplicate a redex, Simon PJ | might know. Yes, it's very careful not to duplicate a redex, except for ones of known bounded size, like x +# y, where sharing the work costs more than duplicating in

RE: -fallow-incoherent-instances

2004-12-03 Thread Simon Peyton-Jones
It is strange that adding -fallow-incoherent-instances should *stop* it compiling. This does not happen in the HEAD. I can see why it happens in 6.2 You are on very very very thin ice with this program. You have instance Confuse a => Typeable a f :: Typeable a => ... f

RE: template haskell printf doesn't compile...

2004-12-03 Thread Simon Peyton-Jones
Sorry Documentation out of date: consult the library documentation for up to date info. Change Expr to ExpQ change string to stringE | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of S. Alexander Jacobson | Sent: 02 December 200

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
riginal Message- | 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 exam

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 if it'

RE: Problems with CABAL in GHC head.

2004-11-15 Thread Simon Peyton-Jones
There have been quite a few changes here including new directories. Make sure you cvs update with the "-d" flag, in both ghc/ and libraries/. And make sure all makefiles and autoconf stuff is up to date. then autoreconf and ./configure. Before doing make, go to ghc/driver and 'make clean'. S

RE: GHC CVS HEAD bug!

2004-11-09 Thread Simon Peyton-Jones
Good point. I've fixed this (HEAD only), and added a test so it won't recur. Thanks! Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Keean Schupke | Sent: 03 November 2004 10:08 | To: [EMAIL PROTECTED] | Subject: GHC CV

RE: Top level mutable data structures problem

2004-10-20 Thread Simon Peyton-Jones
Lots of schemes have been discussed. The one I understand best is: * Modules can contain top-level bindings like x <- e where e:: IO t, and x::t * The IO actions from these bindings are composed, in order of appearance, and together comprise the "module initialisation action" * Wh

RE: Template Haskell...

2004-10-20 Thread Simon Peyton-Jones
newName http://research.microsoft.com/~simonpj/tmp/notes2.ps (sorry for the poor url) Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of MR K P SCHUPKE | Sent: 20 October 2004 15:44 | To: [EMAIL PROTECTED] | Subject: Templ

RE: deriving...

2004-10-20 Thread Simon Peyton-Jones
| Why not even simply | | instance Typeable (T a) | | In other words, derivable classes define default | implementations for all their methods. But that has an existing meaning! It means "use the default methods for all methods of the class". Which is not the same as "derive all methods". It'

RE: deriving...

2004-10-19 Thread Simon Peyton-Jones
Thanks to those who responded to this thread about 'deriving'. My current thoughts are: * I'd be happy to add the ability to separate a 'deriving' clause from its data type declaration, if we can agree syntax (see below). It's fairly easy to do; it makes the language more orthogonal;

RE: deriving...

2004-10-13 Thread Simon Peyton-Jones
(I assume you mean GHC.) Don't look at the compiler, look at the user manual. That describes what's supported. I have no current plans to withdraw any of the current support. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Beha

RE: Mutually recursive modules and derived instances of Data

2004-10-13 Thread Simon Peyton-Jones
| If I have two modules which are mutually recursive; | | module A where | import B | data TA = TA TB deriving (Data, Typeable) | | module B where | import A | data TB = TB TA deriving (Data, Typeable) | | How do I go about writing a hi-boot that will work in GHC? Good question. At the moment

RE: -allow-extension-for-bottom

2004-10-11 Thread Simon Peyton-Jones
On Behalf Of Serge D. Mechveliani | Sent: 11 October 2004 13:32 | To: Simon Peyton-Jones | Cc: [EMAIL PROTECTED] | Subject: Re: -allow-extension-for-bottom | | First, thanks to the people who correct me about `equivalence', | (I skip the name because the letter was addressed privately). | | Because

RE: -allow-extension-for-bottom

2004-10-11 Thread Simon Peyton-Jones
Can you give a small program that runs 1000x faster in one form compared with the other? Currently, if foo is strict, GHC transforms (2) into (1), not the other way round. In general, transforming (1) into (2) looks hard, because it means finding the common portions of two expressions. But I'd b

RE: deriving

2004-10-08 Thread Simon Peyton-Jones
It's all done by the module TcDeriv, which exports one function, tcDeriving, which does all the work. It generates source-code syntax for derived classes. You can grep for where tcDeriving is called (one place in TcInstDcls). Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto

RE: Bools are not unboxed

2004-10-04 Thread Simon Peyton-Jones
| > for :: Int -> IO () -> IO () | > for 0 _ = return () | > for n x = x >> for (n - 1) x Good example (allocates lots of silly thunks). I'd come across this before, and fixed the HEAD, but the 6.2 branch is still doing badly. We'll try to fix that. | Playing with the code generate

RE: constant space `minimum'

2004-09-29 Thread Simon Peyton-Jones
| I meant that the implementation like | | minimum [x] = x | minimum (x:y:xs) = if x > y then minimum (y:xs) | else minimum (x:xs) It would be great if this was the defn of minimum in the Report. But it isn't. Consider da

RE: Deforestation of literal lists

2004-09-29 Thread Simon Peyton-Jones
Carsetn This, plus your earlier message about unfold, certainly make sense. But with the rules below, there's a danger that long literal lists would give rise to a huge nest of cons/build rule firings, which are ultimately all undone again. So I'm a bit cautious about building these rules in. B

RE: ppr styles...

2004-09-06 Thread Simon Peyton-Jones
It's on my list to investigate, but seems harmless. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of MR K P SCHUPKE | Sent: 06 September 2004 11:35 | To: [EMAIL PROTECTED]; [EMAIL PROTECTED]; Simon Marlow | Subject: RE:

RE: boot files...

2004-09-06 Thread Simon Peyton-Jones
You can't, I'm afraid: http://www.haskell.org/ghc/docs/latest/html/users_guide/separate-compila tion.html#MUTUAL-RECURSION To get the instances in the right place, why not just add 'instance Show T' everywhere you find 'instance Putputable T'? I'm not keen on adding Show instances to the main so

RE: Type reps inside GHC...

2004-09-03 Thread Simon Peyton-Jones
RdrName, Name, Id are the three things it gets instantiated to. * Parser generates HsExpr RdrName * REnamer generates HsExpr Name * Typechecker generates HsExpr Id | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of MR K P SCHUPK

RE: Problem with Unboxed Types

2004-08-27 Thread Simon Peyton-Jones
Just to be sure, I've just compiled and run this code with GHC 6.2.1, on a Linux system. I can't account for your difficulty I'm afraid. Simon {-# OPTIONS -fglasgow-exts #-} module Main where import GHC.Exts showUnboxedInt :: Int# -> String showUnboxedInt n = (show $ I# n) ++ "#" main = prin

RE: GHC and MPTCs

2004-08-26 Thread Simon Peyton-Jones
Your problem is that next_state :: forall s v. VertexState s v => s -> s So an application of next_state to an argument of type sty will require the constraint VertexState sty v but that says NOTHING about v. It's a bit like calling a function with type forall a b. Foo a =

RE: overzealous defaulting?

2004-08-24 Thread Simon Peyton-Jones
| I feel that it must be somewhat related to this behaviour: | | Prelude> :t show . read | show . read :: String -> String | Prelude> (show . read) " 13213 " | "13213" | Prelude> (show . read) " 0x1 " | "65536" | Prelude> (show . read) " 1.0 " | "*** Excepti

RE: overzealous defaulting?

2004-08-23 Thread Simon Peyton-Jones
The binding let t = printQ falls under the monomorphism restriction. The Haskell Report would not default (Show a), so you might think you'd get an "ambiguous type variable" error. But it's so annoying to get this error for ghci> show [] that GHCi is a bit more eager about default

RE: What does LIE stand for?

2004-08-19 Thread Simon Peyton-Jones
Yep, "Local Instance Environment". It comes from one of the original papers about giving a formal description for Haskell's type system (in TOPLAS, by Cordelia Hall et al). It's not a very good name. | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL P

FW: Space usage

2004-08-18 Thread Simon Peyton-Jones
d considering in all other respects ghc is far more | sophisticated than my efforts were :-) It does; see my reply below | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Simon Peyton-Jones | Sent: 17 August 2004 17:25 | To: Malcol

RE: Space usage

2004-08-17 Thread Simon Peyton-Jones
| You probably mean | J. Sparud, "Fixing Some Space Leaks without a Garbage Collector", FPCA'93. | http://citeseer.ist.psu.edu/sparud93fixing.html Indeed. | as implemented in hbc. It is also possible to use Wadler's | garbage-collector fix for this space leak, as implemented in nhc98. |

RE: Space usage

2004-08-17 Thread Simon Peyton-Jones
I had a look at this. It's an old chestnut: lazy pattern matching. You have let ((commands, s), x) = run (read iters) 5 in do ...do something with commands... print x Trouble is, the 'x' hangs onto both components of the pair, even though it only needs one. It'

<    7   8   9   10   11   12   13   14   15   16   >