reduced example for ghc-4 `panic'

1998-10-25 Thread S.D.Mechveliani
Here is the reduced `panic' example:ghc-4 -c Bug.hs ft does not look natural. But after `panic' is fixed, i hope the original program will work. By the way, has class PolLike p where cPMul :: Eq a => a -> p a -> p a sense

instance Show (a->b) (was Re: GHC-4.00 assembler crash)

1998-10-25 Thread Felix Schroeter
Hello! On Tue, Oct 20, 1998 at 12:36:44AM -0700, Sigbjorn Finne (Intl Vendor) wrote: > [...] > To quote from somewhere deep within the Prelude: > instance Show (a -> b) where > showsPrec _ _ = showString "<>" > [meta-comment: could we just do away with this one? Beyond giving > rise t

modularity bug in ghc-4

1998-10-25 Thread S.D.Mechveliani
Here is the modularity bug in ghc-4: - module T1 where type Z = Integer toZ= toInteger :: Integral a => a -> Z -- the idea is to switch Z, toZ between Integer, Int - module Main where im

RE: instance Show (a->b) (was Re: GHC-4.00 assembler crash)

1998-10-25 Thread Sigbjorn Finne (Intl Vendor)
Felix Schroeter <[EMAIL PROTECTED]> writes: > > > > To quote from somewhere deep within the Prelude: > > > instance Show (a -> b) where > > showsPrec _ _ = showString "<>" > > > [meta-comment: could we just do away with this one? Beyond giving > > rise to semi-entertaining bugs, it's o

Re: GHC-4.00 Dynamic Heap Sizing

1998-10-25 Thread Simon Marlow
Tim Pollitt <[EMAIL PROTECTED]> writes: > This feature is great, especially for programs which don't have flat > heap usage needs. Finding a good default sizing policy, and a simple > set of controlling options, may be a little tricky. > > >From the GC stats I get the impression that not all li

Re: +RTS -K in ghc-4

1998-10-25 Thread Simon Marlow
"Frank A. Christoph" <[EMAIL PROTECTED]> writes: > I think someone mentioned that GHC 4 can now increase heap size dynamically, so I >assume that -H is just a starting size or a "hint". Dunno about stack, though... Actually, -H is now ignored for compatibility with previous versions :-) -- S

Re: +RTS -K in ghc-4

1998-10-25 Thread Simon Marlow
[EMAIL PROTECTED] (S.D.Mechveliani) writes: > Running the programs compiled with ghc-4 (several examples), i have > noticed that it pretends to spend thousands of space less than > ghc-3.02. Typically, > > ghc-3.02 with +RTS -H100k -K9k runs as fast as > ghc-4with +RTS-K4

Re: Further newbie compilation problems with GHC 4.00

1998-10-25 Thread Simon Marlow
Andrew Cheadle <[EMAIL PROTECTED]> writes: > [compilation output] > > > > ==fptools== make all -r; > in /a/hex/export32/bitbucket/amc4/development/fptools/ghc/lib/std >

Re: GHC 4.00 "Funny global thing?"

1998-10-25 Thread Simon Marlow
Jan Laitenberger <[EMAIL PROTECTED]> writes: > Hi, > > ghc -c -fvia-C -O2 -H45M Resolve.hs > > shows > > NOTE: Simplifier still going after 4 iterations; baling out. > ghc: module version changed to 1; reason: no old .hi file > Funny global thing?: cmUf_btm: > Funny global thing?: cm

Re: bootstrapping ghc on AIX

1998-10-25 Thread Simon Marlow
Jan Kort <[EMAIL PROTECTED]> writes: > It looks like I'm either missing more code, or I'm on the wrong > track. I can't find the powerpc assembly code for "JMP_" (should > be in ghc/includes/TailCalls.h), "StgRun" (should be in > ghc/rts/StgCRun.c) and for "StgReturn" (should be in ghc/rts/StgRun

Re: relocate_TSO

1998-10-25 Thread Simon Marlow
Ralf Hinze <[EMAIL PROTECTED]> writes: > High, Heye, > this is just a short reminder that GHC 4.00 still does not work on my > solaris box. Most programs I run abort with > a.out: fatal error: relocate_TSO > Since you attributed the error to the NCG I tried `-fvia-C', but in > vain. Any h

Re: relocate_TSO

1998-10-25 Thread Simon Marlow
Sven Panne <[EMAIL PROTECTED]> writes: > OK, you've asked for it: Here a picture of ghc-4.00 (CVS snapshot from > Oct 18th, new-rts branch) bootstrapping itself... :-) > >/home/inst/glasgow/linux/bin/ghc -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen >-InativeGen -Iparser >-iutils:basicT