Re: Recovery from parser stack overflow

1997-03-26 Thread Simon L Peyton Jones
| I'm trying to compile a module that looks like this: | | ---begin | module PLib where | import Common | gr_lib = | ---end | | GHC comes up with: | | "PLib.hs", line 3, column 476908: parser stack overflow on input: ""i"" This is fixed in 2.02 (available later today or early tomorrow). I

Re: Prelude not imported qualified in GHC 2.02

1997-03-27 Thread Simon L Peyton Jones
Good point! I didn't implement that special case (which I should have). A better fix would be to say that "hiding" hides only the unqualified name. The report is vague on this matter! I'll try to get it clarified. Meahwhile, you can always add "import qualified Prelude" yourself, as a worka

Re: 2.02 and parser errors and interface errors

1997-03-26 Thread Simon L Peyton Jones
Thanks for the bug reports. | (1) GHC can't parse its own interface file? | I have a parser which I compiled with ghc. Any file which imports | from this, such as | | > module Foo where | > import Parser | > foo = "A" | | dies with: | Foo.lhs:3: | Interface-fil

Re: 2.01: fromEnum & toEnum missing when deriving instances

1996-11-22 Thread Simon L Peyton Jones
This is a bug in the deriving code... Haskell 1.3 added a method and we didn't derive code for it! I'm fixing it in my copy so it'll appear in the next release, which I'm now planning. Simon | From: Magnus Carlsson <[EMAIL PROTECTED]> | Date: Fri, 25 Oct 1996 00:27:21 +0200 (MET DST) | Compili

Re: Stand-alone parser

1996-11-22 Thread Simon L Peyton Jones
Stephan (I don't have your personal email address) Is this still a live issue for you? If so I'll do something about it. Simon | From: [EMAIL PROTECTED] | Date: Mon, 4 Nov 96 17:18:27 GMT | | Stephan Tobies writes: | | >There has been a stand-alone version of the parser in version 0.29. |

Re: 2.02 and parser errors and interface errors

1997-03-26 Thread Simon L Peyton Jones
This one is a straightforward parser bug. The fix is quite easy, but I can't see a workaround (other than getting source and doing the fix). I guess the workaround is to leave out the annotation. So I'm afraid it's just "fixed in the next release". Incidentally, we're planning to make fairly r

Re: 2.01: Missing interface declarations for selector functions?

1996-11-22 Thread Simon L Peyton Jones
This bug has gone away in the Glorious New Renamer. Simon | From: Magnus Carlsson <[EMAIL PROTECTED]> | Date: Tue, 15 Oct 1996 18:55:29 +0200 (MET DST) | When compiling the two modules | | module Geometry where | data Point = Point {xcoord,ycoord::Int} | | and | | module X where | im

Re: bug report

1996-12-05 Thread Simon L Peyton Jones
| > module A( B ) where | | > data B = C a This isn't legal Haskell: data constructors can't mention type variables not bound on the left hand side. This would be legal > data B a = C a But it still shouldn't crash the compiler! Thanks for the bug report Simon

Re: Bus error (core dumped)

1997-04-08 Thread Simon L Peyton Jones
Ralf Thanks for identifying this bug. Our test suite didn't have a program with duplicate "main" definitions. (It does now!) Workaround: don't duplicate top level defns. It'll work in the 2.02-patched release. Simon | From: Ralf Hinze <[EMAIL PROTECTED]> | Date: Mon, 7 Apr 1997 11:04:38 +0

Re: More of same.

1997-01-29 Thread Simon L Peyton Jones
Alex I'm deeply disinclined to follow this one up because we're preparing GHC 2.02 for release. It has a whole new front end, so the bug is unlikely to be there (different ones will :-)). Here's an offer: tar up the Haskell sources of your system and send them to me, and I'll try to compile th

Re: parse errors

1997-01-31 Thread Simon L Peyton Jones
Urk! Yes, we took them out of 2.01 because we thought they were gone from Haskell 1.3. Then they were resurrected, but we didn't get around to putting them back into 2.01! And then in the hiatus of last autumn I forgot all about them. I'll put them back into the soon-to-be-released 2.02. Si

Re: panic! (the `impossible' happened): deListComp:LetQual

1997-02-05 Thread Simon L Peyton Jones
| ghc has trouble compiling let expressions inside list comprehensions. | when i replace let foo =3D bar with foo <- [bar], then everything seems | to work. | | is this a known bug? (if no, do you need example files that reporduce it?= | ) | | is my workaround morally correct (strictness, polym

Re: Error in 2.01 -recomp

1997-02-12 Thread Simon L Peyton Jones
| If a new symbol is added, (apparently) no test is made to see if this | causes a clash with existing symbols in higher-level modules. | | Also, moving a function from one module to another sometimes confuses | the recomp system, when it's looking for it in the "old" place: eg: Both of these

Re: Space leak

1997-04-08 Thread Simon L Peyton Jones
| I need some expert help on a program of mine. The program benchmarks | several implementations of functional priority queues. Basically, it | evaluates different expressions using different implementations of | priority queues: binary heaps, Braun heaps, pairing heap, leftist heaps | etc. I th

Re: It done broke my parser.

1997-03-10 Thread Simon L Peyton Jones
For 2.02 I've fixed the parser to use left recusion instead of right recursion. That will make the parser use much less stack. The Haskell compiler itself should probably have some special case stuff for very large literal lists. I havn't done anything about this, but at least it'll get past

Re: ghc-2.01 in knots.

1997-03-10 Thread Simon L Peyton Jones
| Has anyone found a problem with (erroneously, in my case) knot-tied | structed pattern matching? I got a bus error (eek) from a fragment | of the form: | | blah b = ... x ... |where |[x] = ... [x] ... | | While I'm fairly sure this is what caused the problem, (I did a clean |

Re: Compiling GHC

1997-04-09 Thread Simon L Peyton Jones
Jon | Well I am about to bite the bullet and try and make GHC compile | GHC so that I can use your patches. I'd be delighted if you did. The big thing is that you have to make the .hi-boot files to get things started for mutually recursive modules. This needs to be done differently than for 0.

Re: Haskell compiler

1997-04-22 Thread Simon L Peyton Jones
| From: Janos Blazi <[EMAIL PROTECTED]> | Date: Sun, 13 Apr 1997 16:17:56 +0200 | Hallo! | | I teach at a German grammar school and Haskell would be a wonderful = | language for teaching Infomation Technologies. But I think istallation = | is hopeless for a UNIX-illiterate like me. (I use NT 4.0

Re: Big heap for a small program

1997-04-30 Thread Simon L Peyton Jones
Marc Thanks for reporting this error. It turned out to be an error in the error recovery in the type checker. Easily fixed; but it's not fixed in 2.03. Simon | From: Marc van Dongen <[EMAIL PROTECTED]> | Date: Wed, 9 Apr 1997 14:06:39 +0100 (BST) | I just wanted to report that the erroneous

Re: incomplete pattern warnings

1997-05-07 Thread Simon L Peyton Jones
| From: Chris Okasaki <[EMAIL PROTECTED]> | Date: Mon, 05 May 1997 15:41:51 -0400 | Minor problem with the check for incomplete patterns: | | Under ghc-2.02, the following program gives a warning about | "Possibly incomplete patterns in the definition of function `f'" | even though the pattern

Re: to and fro

1997-05-13 Thread Simon L Peyton Jones
| a never ending story: the Haskell Library and its constituents. | `group' and `groupBy' did not make into the List library: ... and a bunch of others. I've fixed it in our upcoming source release. Thanks for reporting this. Simon

Re: status of the powerpc port of ghc ?

1997-05-15 Thread Simon L Peyton Jones
Mari Andre Santos ([EMAIL PROTECTED]) was quite far along with an RS6000 port. I should contact him before doing much. I think he may have stopped pending a self-bootable version of GHC, which we now have and are about to put out. Well done porting to MPI. I'm very interested to hear how that

Re: Bug in Concurrent Haskell

1997-05-15 Thread Simon L Peyton Jones
Thanks. Fixed in next release. Simon | From: Meurig Sage <[EMAIL PROTECTED]> | Date: Thu, 15 May 1997 19:37:14 +0100 | There's a bug in the signalQSemN function in the | Semaphore module. (In versions ghc-0.29 through 2.03).

Re: Minor minor bug (tlist) in ghc-2.01 leads to panic...

1997-05-15 Thread Simon L Peyton Jones
| I couldn't fix. But I played around with it, I found a small little | script which reproduces it very well: | | > type state = ([Int] Bool) ... | panic! (the `impossible' happened): | tlist This bit me some while ago, so don't be embarassed about writing an incorrect program! Anyway,

Re: Pattern guards

1997-05-15 Thread Simon L Peyton Jones
| > f c | (i,j) <- Just (toRect c) = ... | | I'm afraid this example suffers from the same problem as my "simplify" | example did: It does not perform a test and can thus be replaced by | | f c = ... | where (i,j) = toRect c True. I can think of two non-contrived ways in which this

Re: [bug report] ghc-2.03: wrong (!!) fixity; instances for `newtype'

1997-05-21 Thread Simon L Peyton Jones
Tomasz, Thanks for the fine bug reports. Keep em coming. | Source of the problem is a declaration in PrelBase.lhs: | infixr 9 !! | According to the Report it should read: | infixl 9 !! Fixed. | 2. The following code | | > newtype Age = MkAge Int deriving (Eq, Show) | > instance Num (Ag

Re: [bug report] ghc-2.03: exponential number of error messages

1997-05-22 Thread Simon L Peyton Jones
| Each additional, no matter how trivial definition causes that the | compiler starts to produces twice as many error messages. In general | adding n definitions gives raise to 7 * 2^n errors, e.g., adding: Yes, I tripped over this too! It could only happen in a compiler written in a functiona

Re: [bug report] labeled fields in ghc-2.03

1997-05-20 Thread Simon L Peyton Jones
Thanks for the bug report. What you say is all too true. It's fixed in my working copy; pending the next release I guess you'll just have to work around it. Sorry. Simon | From: Tomasz Cholewo <[EMAIL PROTECTED]> | Date: Tue, 20 May 1997 05:10:04 GMT | Hi, | | ghc-2.03 cannot compile the fo

Re: Eval (a -> b) instance

1997-06-18 Thread Simon L Peyton Jones
| just wanted to let you know that `a -> b' ist not made an instance of | `Eval'. The following piece of code demonstrates the shortcoming. Good point; thank you . Simon

Re: Windows 95 GHC

1997-06-19 Thread Simon L Peyton Jones
Ed | I'd love to get GHC 2.0x working on my PC, but I note the following: We plan to put together a Windows binary release of GHC early next week. Simon

Re: data dependencies broken by an optimisation pass

1997-06-18 Thread Simon L Peyton Jones
Isn't it wonderful how real users find bugs so much faster than implementors. Thanks Ralf. It's my fault. Now fixed in my copy. Unfortunately there's no workaround. I can see we're going to have to push out 2.05 in some form. Simon | From: Ralf Hinze <[EMAIL PROTECTED]> | Date: Tue, 17 Jun

Re: Allegedly ambiguous functions:

1997-06-23 Thread Simon L Peyton Jones
The reason that 2.02+ complain where earlier versions don't is that I must have implemented polymorphic recursion in 2.02. Under polymorphic recursion it is indeed ambiguous at what type to call "g" in the recursive call. We have yet to see whether this bites in real programs rather than mega-t

Re: bug report

1997-05-30 Thread Simon L Peyton Jones
Good report! The contexts on the signatures in a mutually recursive group must be the same (i.e. unifiable), but GHC wasn't being careful enough.. here they aren't even the same length. Embarassing, but easily fixed. Simon | From: Marc van Dongen <[EMAIL PROTECTED]> | Date: Fri, 30 May 1997 1

Re: labelled fields in ghc-2.04

1997-06-18 Thread Simon L Peyton Jones
| data X = A {a :: Int} | B {a :: Int} | -- | test2.lhs:2: | Conflicting definitions for: `a' | Defined at test2.lhs:3 | Defined at test2.lhs:3 Embarassing, but all too true. There's really no workaround for this. GHC 2.04 is stupidly unable to have

Re: Using "->" in an instance

1997-07-02 Thread Simon L Peyton Jones
| I have a class of kind * -> * -> *, and want to make an instance of | this class for the "->" constructor. Hugs allows this, and (at least | according to the error message) GHC does not; it gives a "constructor | not in scope" error message when I try. The Report says that "->" is | an abstra

Re: Not very Happy.

1997-07-24 Thread Simon L Peyton Jones
Alex | Further to my previous comments about ghc-2.04 and Happy output, I | can report that having mangled happy-0.9 output to work with 1.4ish | arrays, the situation is more dire yet. For the same happy input | program as previously reported, ghc _really_ struggles to compile | the -a output

Re: GHC's internals

1997-07-25 Thread Simon L Peyton Jones
| -dppr-all | gives less information than -dppr-all (e.g. no types, no identifier | uniques); looks more like what you would expect of -dppr-user; | however, even a user will probably want types. | | -dppr-user | output identical to -dppr-all except that all identifiers are | enclos

Re: tcLookupTyVar error (Similar as last one? Don't know.)

1997-06-17 Thread Simon L Peyton Jones
Marc, GHC 2.04 doesn't crash. It says: tc086.hs:56: Context required by inferred type, but missing on a type signature arising from use of `compare' at tc086.hs:51 `Group' `a{-aIG-}' When checking signature(s) for: `multiply' In an equation for fu

Re: bug report

1997-06-17 Thread Simon L Peyton Jones
Marc, GHC 2.04 correctly says Main.hs:17: Ambiguous overloading arising from use of `g' at Main.hs:23 `PrelBase.Ord' `p{-a17v-}' When checking signature(s) for: `g' | From: Marc van Dongen <[EMAIL PROTECTED]> | Date: Sat, 31 May 1997 14:35:40 +0100 (BST

Re: Where is ghc/docs/state-interface.dvi ???

1997-06-17 Thread Simon L Peyton Jones
| So my question is: | | -- how do I convert an unboxed value to a boxed value? | | -- where on Earth is state-interface.dvi? It's now incorporated as part of the user manual. Sorry for the stale pointer. You might find it helpful to read "Unboxed values as first class citizens" to learn h

Re: question

1997-06-17 Thread Simon L Peyton Jones
Marc, | Could somebody tell me how to disambiguate the following program | | > module Tmp( g ) where | > data A p q = A | > g :: (Num p,Ord q) => (A p q) -> Bool | > g A = g A I don't understand this. "g" always returns bottom. | I could do something like | | > g a@A = a That's different!

Re: bug report

1997-08-18 Thread Simon L Peyton Jones
> > > module Strange( strange ) where > > > > > strange :: (a,a,a) -> a > > > strange triple > > > | (first triple) == (fst triple) = first triple > > > > > first :: (a,b,c) -> a > > > first (a,b,c) > > > = a > > > > Stange.lhs:5: Couldn't match the type > >`PrelTup.(,,) t

Re: Local universal quantification

1997-08-15 Thread Simon L Peyton Jones
> like `callcc'. Let's have a closer look: the code of `callcc' contains > the subexpression `KContT (\cont' -> cont a)'. To be well-typed the > argument of `KContT' must have the type `(All res) => (a -> m res) -> m > res'. Quantification is not possible, however, since the type variable > in `c

Re: `Better' error messages

1997-08-19 Thread Simon L Peyton Jones
> > ghc -c Sequ.lhs > > Sequ.lhs:21: Mismatched contexts > When matching the contexts of the signatures for `foldr' and `member' > (the signature contexts in a mutually recursive group should all be >identical) Thanks for this bug report. I had done some house-cleaning on TcClas

Re: Local universal quantification

1997-08-19 Thread Simon L Peyton Jones
> I *suppose* that there is a bug in GHC's type checker. The following > program, which I think is ill-typed, passes silently the type checker. > Needless to say that it uses some of GHC's arcane type extensions. Well, the code was just plain wrong (in checkSigVars in TcBinds.lhs). Here's the ne

Re: Something cooking with forkIO

1997-08-20 Thread Simon L Peyton Jones
> Then I increased the number of threads to 1M, and got: > > ewk@hydra% bench1 > Heap exhausted; > while trying to allocate 32 bytes in a 4194312-byte heap; > use `+RTS -H' to increase the total heap size. > > I now obediently ran the program with 16MB heap: > > e

Re: some array questions

1997-08-20 Thread Simon L Peyton Jones
Josh > Some questions about arrays: > It sounds like, according to this specification, there has to be a thunk > for every element of the array. This brings up the usual trade-off: this is > elegant and flexible, but slow. > ??? - For generic GHC Array's, is a thunk created for each individ

Re: two minor questions on ghc

1997-08-20 Thread Simon L Peyton Jones
> (1) > To make ghc-2.04 putting .o files into the given subdirectory, > say, `o_hi', we command > ghc -c Foo.hs -odir o_hi > > What is the similar option for .hi ? > I cannot find it in the ghc user guide. It suggests only > > ghc -c Foo

No Subject

1997-08-21 Thread Simon L Peyton Jones
> When I compile the following short part of a program using ghc-2.01, > I encounter a compiler bug. I am not sure that it is the one you ask > programmers using the compiler to report. It sounds to me as if the > compiler doesn't support the use of the expression 'let' in list > compression. Ye

Building GHC's libraries

1997-08-19 Thread Simon L Peyton Jones
Ralf, Olaf, Sven, and others building GHC, In your build.mk file you should typically include -O in the library build flags GhcLibHcOpts=-O -H25m If you don't, the prelude is built un-optimised. That in turn means that even "+" won't be inlined, and you get pretty terrible cod

Re: ghc-2.05 v. happy1.2-a

1997-08-27 Thread Simon L Peyton Jones
> PrelTup_Z40Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44 > Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z4 > 4Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z44Z41_con_info > Galileo6.o > ld: fatal: Symbol referencing err

Re: Compiler Crash: ghc-2.05:panic! lookupBindC:no info!

1997-09-03 Thread Simon L Peyton Jones
> The following program (rather condensed as it comes from something > much larger), crashes the compiler. I am using ghc-2.05 on a Solaris > box, with one or two patches(including the WwLib one which Simon gave > me, but this error occured before applying this patch). Thanks for this bug report

Re: profiling optimised code

1997-09-08 Thread Simon L Peyton Jones
> Main.o(.text+0x9c): undefined reference to `PrelBase_Z36g3J_fast3' That's odd. It's usually a sign that PrelBase.hi and PrelBase.o weren't generated by the same run of GHC. You could try doing "make clean; make depend; make" in your ghc/lib directory. If that doesn't work we'll need to inve

Re: building with ghc-2.03

1997-09-08 Thread Simon L Peyton Jones
> Hi ! > I am trying to build ghc-2.05 libraries with ghc-2.03 on RS6000 and > get the following problem: That's a very curious thing to do! You should only compile the ghc-2.05 libraries with ghc-2.05. The format of interface files has changed often. The complaint you are getting is that ghc-2.

Re: Too lazy ...

1997-05-30 Thread Simon L Peyton Jones
Yes, GHC more or less ignores seq at the moment. That's an advertised shortcoming, but one that won't get fixed till I do my cg/rts housecleaning operation, scheduled for the autumn! Simon | ghc generates code which is sometimes a bit too lazy. Consider the | following program | | > main

Re: bug report

1997-05-30 Thread Simon L Peyton Jones
Marc you are outstanding at winkling out these bugs. This is an erroneous program because 0 doesn't have type (forall a.a), but it should not crash the compiler. I've fixed it in 2.04. Simon | From: Marc van Dongen <[EMAIL PROTECTED]> | Date: Thu, 29 May 1997 22:38:32 +0100 (BST) | Compiling t

Re: another one

1997-05-30 Thread Simon L Peyton Jones
| I cannot think of any reason why compiling the following | two programs should give different results. Maybe some deep | reason? I can! | > module Rings( Group ) where | | > import qualified Prelude( Num(..) ) | > import Prelude hiding( Num(..) ) | | | > class Group a where | > negate ::

Re: bug with unboxed types

1997-05-28 Thread Simon L Peyton Jones
It's a terrible error message, but you can't instantiate polymorphic types with unboxed arguments. So you can't have a tuple with unboxed args. Simon | > foo :: Double# -> (Double#,Double#) | > foo d = (d,d) | | produces :- | | > /local/fp/bin/sparc-sun-solaris2/ghc-2.02 -H1000 -i/user

Re: Derived instances with newtype

1997-05-29 Thread Simon L Peyton Jones
Yes, this is the same but as Tomasz Cholewo reported. It's a bug and it'll be fixed. (Nearly done, actually.) many thanks for the report. Simon | ghc-2.03 gets a little confused when deriving instances from newtype | declarations: Compiling | |module Main where |newtype Foo a = Bar

Re: Readline beats 2.05

1997-08-19 Thread Simon L Peyton Jones
> After my patch/hack hsc built fine, but now the new compiler and Readline > don't like each other. The relevant part from the compilation log: > >[ almost 5900 highly entertaining lines removed... ] >../../ghc/driver/ghc -O -H32m -split-objs -odir src/Readline -I -recomp >-isrc:../po

Re: GHC 2.05 bug

1997-08-19 Thread Simon L Peyton Jones
> When compiling a (rather long) file with GHC 2.05, compiled with GHC > 0.29 on a Linux box, I got the following error: > > Fail: "basicTypes/Id.lhs", line 990: incomplete pattern(s) to match in function >"dataConFieldLabels" Squashed it. The fix will be in 2.06. The workaround is to avoid d

Re: 100 MB of heap exhausted when compiling Happy

1997-09-22 Thread Simon L Peyton Jones
> When compiling Happy-1.3's Main.lhs with optimization turned on, 100 MB of > heap space aren't enough for the compiler. It crashes after several hours > of compilation. When optimization is turned off, it finishes after some > minutes. I would consider this a bug. I consider it a bug too!

Re: Building ghc-0.29 for on sunos4 and linux

1997-10-23 Thread Simon L Peyton Jones
What is happening is this. - there's a SPECIALISE pragma involving data type Reg in FiniteMap - SpecTyFuns imports FiniteMap - Haskell 1.2 required closure on import, so Reg therefore had to be imported even though it's not used. Haskell 1.4 doesn't have this silly restriction. Solution: i

Re: Optimizing Haskell programs is hard

1997-10-17 Thread Simon L Peyton Jones
You are right to be "bugged" (see your last para). Fortunately, ghc 2.09 (i.e. our current working copy) gives identical runtimes for all three. (Might be true of 2.08; I haven't tried.) Simon > I'm benchmarking MVar's and other shared memory abstractions, e.g. by > accessing a variable a nu

Re: BUG FOUND

1997-11-07 Thread Simon L Peyton Jones
Thanks for the fine bug report. It'll be fixed in the next release. Simon > I found a compiler bug in 'ghc', it came up as follows: forgetting a > definition, e.g. 'atMost', in a signature, but still keeping a default method > for 'atMost' should produce something like > > TestADT.lhs:

Re: 0 = 1

1997-11-20 Thread Simon L Peyton Jones
> I can't remember having seen anything like this before. > The following program compiles fine with ghc2.0698 > > > module Main( main ) where > > > main = return () > >where 0 = 1 Looks fine to me. The pattern "0" is matched lazily, that is when any of its free variables

Re: kind disagree in interface

1997-11-20 Thread Simon L Peyton Jones
> ghc-2.08-linux reports > > : Couldn't match the kind >`ka10725 -> *' against `*' > When unifying two kinds `* -> *' and `*' > In an interface-file signature for `$gL' > > > Many types have been modified in the module to include the additionl > type

Re: pragma closing at new line

1997-11-21 Thread Simon L Peyton Jones
Looks like a bug all right. (I get a parse error.) We'll look at it. Meanwhile, its easily avoided. Remember, too, that 2.08 still doesn't have a specialiser, so the pragama ain't helping. Sorry about that. Simon > ghc-2.08-linux reports that `#-}' is wrongly placed in the program: >

Re: Again: The impossible happened, this time in 2.08

1997-11-27 Thread Simon L Peyton Jones
Great bug report, thanks. I've fixed it in the upcoming 2.09 S > As a by-product of hacking Fudgets to death, a bug in ghc-2.08 showed up. > Compiling the fragment from Fudgets below (the real names made as much > sense to me as the ones below :-), ghc fails ungracefully: > >

Re: Overlapping instance declarations.

1997-12-10 Thread Simon L Peyton Jones
> "A type may not be declared as an instance of a particular class more than > once in the program." > > Doesn't it really mean that a type _constructor_ may not appear in more > than one instance declaration for a particular class? That (stronger) > condition seems to be what ghc and hugs impl

Re: problem adding phase

1997-12-19 Thread Simon L Peyton Jones
> I am trying to add an optimisation phase to ghc and get the > following error message. Is there a simple way for me to > fix this ? (I am trying to generate code variants.) > > panic! (the `impossible' happened): > lookupBindC:no info! > for: Main.m{-r1IZ-}{-r1IZ-} {- Int/EXP(..){-2i-}

Re: -recomp oddness.

1997-12-20 Thread Simon L Peyton Jones
> I'm not sure if this is Known Deficiency or not, but ghc-2.09 -recomp > still seems to get confused when new exported items have been added to > a module, on which the -recomp'd module depends. It misses any (or > at least, some) name-clashes, until some later point when recompilation > is for

Re: panic! (the `impossible' happened) (2.09, patchlevel 0)

1997-12-19 Thread Simon L Peyton Jones
> {- >Hi, > >Compiling the following module results in the following error message >(with GHC 2.09, patchlevel 0, i386-linux > > > -- >panic! (the `impossible' happened): > getWorkerIdAndCons area

Re: ;

1997-12-23 Thread Simon L Peyton Jones
> unfortunately I did not succeed in installing GHC from source. Probably > I'm missing something. Here is a short summary of my trial: Simon Marlow is away now till after Xmas, so I fear you're on your own till then! Simon

Xmas fun

1997-12-19 Thread Simon L Peyton Jones
Folks, I thought you might find the following bug I've just found in GHC entertaining. In the strictness analyser we need to compare abstract values so that the fixpoint finder knows when to stop. In the middle of this code was the following: sameVal :: AbsVal -> AbsVal -> Bool

Re: Xmas fun

1997-12-30 Thread Simon L Peyton Jones
> This bug could have been caught by a very simple static analysis that > is very popular in the logic programming community: singleton variable > warnings. In the code above, the variable `v2' occurs only once. > Singleton variables such as this are often bugs. For cases where the > programmer

Re: Mysterious 2.09 message.

1998-01-09 Thread Simon L Peyton Jones
> Alex Ferguson writes: > > > > Struct.hs:1: Failed to find interface decl for `Maybe' > > > > Compilation had errors > > make: *** [Struct.o] Error 1 > > > > > > I'm guessing it has to do with out of date interface files (from ghc-2.07, > > to be exact), but it's not the most helpful way of

Re: The impossible, again...

1998-01-26 Thread Simon L Peyton Jones
> > Hi everybody-peeps. I stumbled across the following panic, which occurs > when I compile the given module with either -O2 or -O. If it proves > necessary I'll try to produce a small instance, ship the whole lot off > to Glasgow, or otherwise poke around in search of illumination. Try with

Re: newtype error

1998-01-26 Thread Simon L Peyton Jones
Dead right. Thanks for the report. Will fix. Simon > I tried > > newtype LTSState = MkLTSState Int# > > and got > > *** Pattern-matching error within GHC! > > This is a compiler bug; please report it to > [EMAIL PROTECTED] > > Fail: "basicTypes/Id.lhs", line 920: incomplete pattern(s) t

Booting GHC

1997-10-03 Thread Simon L Peyton Jones
> while trying to compile GHC 2.07 with 2.02 (on i386 Linux) I > encountered the following: I think we are guilty of not making the following clear: GHC 2.01 - 2.06 are INCAPABLE of compiling any version of GHC To compile GHC you need 0.29, or 2.07 (or later, of course). Simon

Re: Profiling, again.

1998-01-26 Thread Simon L Peyton Jones
> > Another non-killing, but rather annoying error message: this one is > provoked by duplicate _scc_ labels. I don't see the sense in this > restriction, myself, but at any rate this wouldn't seem to be the > handiest way of detecting same... > > Cheers, > Alex. Thanks -- this is another of

Re: Profiling again.

1998-01-26 Thread Simon L Peyton Jones
> Doing a time-profiling of my current hackery tells me the worst offender > in my program is: > > Intervals/$d11 > > This raises and question or two in my mind... > > This represents the encoding of a dictionary (or a single method?) > for some class with an instance declared in the gi

Re: cyclic module dependencies

1998-01-28 Thread Simon L Peyton Jones
> Only why the ghc implementors keep on saying the mutually recursive > modules is a headache? > The bold-naive question arises: > if ghc compiles, - without warning and without asking the order of > compilation, - the mutually recursive functions f, g, why cannot it > do this "similarly" for

Re: Compiler bug pops up when compiling ghc-2.07 with 2.02

1997-10-09 Thread Simon L Peyton Jones
> > I tried, but it seems to complete successfully. Nevertheless, later > make all fails with the same message. > Probably the dependencies generated by make boot (or make depend, for > that matter) _are_ circular (citing from ghc/compiler/.depend): > > utils/FastString.o : basicTypes/Unique.hi

Re: Pattern-matching strings.

1998-01-28 Thread Simon L Peyton Jones
> > Is pattern-matching short strings (one or two characters) likely to be > _vastly_ less efficient than matching against a single level of > constructor? (Order of magnitude, plus.) Trying to make sense of some > profiling numbers, here... I believe it is. Currently I think we call the over

Re: Strange module exportation behavior

1998-01-29 Thread Simon L Peyton Jones
Conal: great bug report; thanks. Meanwhile a workaround is to use qualified names in the export list for Test2: module Test2( Test1.foo, module Test2 ) import Test1 hiding(main) main = ... Inconvenient, but it should get you rolling. Simon, Si

Re: Fun with 3.00

1998-01-29 Thread Simon L Peyton Jones
> One can play funny games with GHC-3.00 and the following program > (a small fragment of a Happy-generated parser): > > -- > module Foo ( happyParse ) where > > action_0 1 = \j tk _ -> action_1 j j tk (HappyState action_1)

Re: Query on multi-param type classes

1998-01-30 Thread Simon L Peyton Jones
> I decided to try and get my old multi-param. parser to work, > and got told-off by Haskell's parser: > > Please tell me what I am doing wrong. The following program: > > > module A where > > > > class (Monad m, Monad (t m)) => AMonadT t m where > > lift :: m a -> t m a > > Gives me: >

Re: building ghc on new platform

1998-01-27 Thread Simon L Peyton Jones
Richard > Is it true that one must have a working version > of ghc on a new in order to port it to that platform > or is there a "starters-kit" with which one can > start such a port? You can port by starting from the ".hc" files; that is, files that have been compiled to C but not to machine c

Re: instance again

1998-02-05 Thread Simon L Peyton Jones
> After trying a bit more, I found out how to fix the problem. > > > > data Blah = Blah > > > type Tuple = (Blah,Int) > > > instance Eq Blah > > instance Ord Blah > > instance Read Blah > > instance Show Blah > > Adding the previous 4 dummy instance declarations makes > this fragment to b

Re: MPC Feature/Error ?

1998-02-05 Thread Simon L Peyton Jones
> > My first attempt to define a MPC and some instances failed partially. > > I am not sure, if it is a bug or a feature. The class OMSObjAttrAppC > > should restrict the possible combinations of objects and attributes, > > so that attributes can only be read from objects to which they > > belong

Re: GHC 3.00 Bug or New Restriction ????

1998-02-06 Thread Simon L Peyton Jones
> > Ok, it's a bit of a pain to put the extra constructors everywhere, but > > at least you don't lose any efficiency. > > Is that `True'? Does the compiler spot identity functions like > `map ListBlah'? No it does not. That's one of the reasons I'd like to replace newtype with some sort of typ

Re: Misleading error message

1998-01-27 Thread Simon L Peyton Jones
Manuel: Thanks for the suggestion. Is this better? Simon Foo.hs:8: Couldn't match the type `()' against `[aVG]' Expected: () Inferred: [aVG] In the second argument of `:', namely `()' In a "case" branch: [] -> 1 : () Foo.hs:3: Couldn't match the type

Re: The impossible, again...

1998-01-27 Thread Simon L Peyton Jones
> panic! (the `impossible' happened): > lookupBindC:no info! > for: showsPrec_a7AK Alex tickled a genuine, long-standing bug in the simplifier. Congratulation! Here's the patch, to simplCore/Simplify.lhs Simon == diff -c /users/fp/simonpj/fptools-

Re: bug report

1998-02-05 Thread Simon L Peyton Jones
Mark says: > > data Blah = Blah > > type Tuple = (Blah,Int) > > > instance Show Tuple where > > showsPrec _ _ _ > > = error [] > > No instance for: `Show Blah' > arising from use of `PrelBase.$mshowList', at tmp.lhs:8 > > I know that instances of classes shouldn't be types,

Re: GHC 3.00 Error when introducing an ErrorMonad

1998-02-06 Thread Simon L Peyton Jones
> While experimenting with multiple parameter type classes, I > introduced an ErrorMonad. Compiling this with GHC 3.00, the > following happened: > > Computation.hs:16: Warning: > `ErrorMonad' mentioned twice in export list I'll look into this. > panic! (the `impossible' happened): >

Re: bug report 3.00

1998-02-06 Thread Simon L Peyton Jones
> > panic! (the `impossible' happened): > > fun_result_ty: 6 GHC.Int#{-3e-} > > -> GHC.Int#{-3e-} > > -> b_trKC > > -> PolyParse.HappyState{-rq9-} b_trKC c_trKD > > -> [PolyParse.HappyState{-rq9-} b_trKC c_trKD] > >

Re: Strange time behaviour without optimisations

1998-02-07 Thread Simon L Peyton Jones
> I know that ghc performs hardly any optimisation if called without -O or -O2. > However, is it necessary that just adding a single function definition to a > program *without* calling this function increases execution time by 50%? > (ghc-2.08) That is odd However, I tried your example with 2.10

Re: Is this a bug???

1998-02-09 Thread Simon L Peyton Jones
> Test.hs:13: > Too many parameters for class `ParentWidget' > In the class declaration for `ParentWidget' I think you must have omitted -fglasow-exts as Sigbjorn says. The code that generates the error is this checkTc (opt_GlasgowExts || length tyvar_names == 1) (clas

Re: Another panic

1998-02-06 Thread Simon L Peyton Jones
> The following works fine with GHC 3.00: > > class Variable v where > updVar :: v a -> (a -> IO (a,b)) -> IO b > > applyVar :: Variable v => v a -> (a -> a) -> IO a > applyVar v f = updVar' v (\x -> let x' = f x in (x',x')) > > By changing the definit

  1   2   >