reduced example for ghc-4 `panic'
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? I thought, yes. -- Sergey Mechveliani [EMAIL PROTECTED] --- class PolLike p where cPMul :: Eq a => a -> p a -> p a class Eq a => AddSemigroup a where add :: a -> a -> a type UMon a = (a, Integer ) type Monomial a = (a, [Integer]) data UPol a = UPol [UMon a] a String [a] instance Eq a => Eq (UPol a) instance PolLike UPol where cPMul _ _ = error "" instance Eq a => AddSemigroup (UPol a) ft :: AddSemigroup k => UPol k -> [UPol k] ft f@(UPol _ c v d) = let berl h = let b = [cPMul c h] fr = map (const []) [cPMul c h] in case head fr of _:_ -> let es = map (add (UPol [] c v d)) [h] in berl h in berl f
instance Show (a->b) (was Re: GHC-4.00 assembler crash)
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 to semi-entertaining bugs, it's of precious little practical use..] I think, it IS of practical use for hugs users, as it prints <> as a response of a function valued expression instead of an error message that it can't find an instance of Show for the type of the entered expression. > Thanks for the report; fixed (one line patch attached.) > --Sigbjorn > begin 600 MachRegs.diff Why not in clear text? :-) > [... uuencode deleted ...] Regards, Felix. PS: The Message-Id in your mail is a bit strange. Usually, it should be <[EMAIL PROTECTED]>.
modularity bug in ghc-4
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 import List (genericTake) import T1 (Z, toZ ) f :: Z -> Z -> [Z] fni = case toZ i of j -> genericTake (n+j) (repeat n) main = let ns = f 2 3 in putStr (shows ns "\n") - After ghc -c T1.hs, ghc -c Main.hs the compiler derives a contradiction for i :: Int, Z. After moving the definition of toZ to Main.hs the compiler solves the types differently. -- Sergey Mechveliani [EMAIL PROTECTED]
RE: instance Show (a->b) (was Re: GHC-4.00 assembler crash)
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 of precious little > practical use..] > > I think, it IS of practical use for hugs users, as it prints > <> as a response of a function valued expression instead > of an error message that it can't find an instance of Show for the > type of the entered expression. > That's a Hugs user interface issue, and can be solved without polluting the Haskell Prelude, i.e., no need to burden the rest of us with it ;-) > > > begin 600 MachRegs.diff > > Why not in clear text? :-) > because Outlook scares me no end :-) > > [... uuencode deleted ...] > > Regards, Felix. > > PS: The Message-Id in your mail is a bit strange. Usually, it should > be <[EMAIL PROTECTED]>. > Maybe so, but it's within the bounds of what constitutes a legal addr-spec as per RFC 822. --Sigbjorn
Re: GHC-4.00 Dynamic Heap Sizing
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 live structure is > accounted as heap. If some objects (eg. arrays) incurring GC costs are > ignored by resizing decisions, then it's possible for the collector to > recover nearly all of a tiny heap, but spend nearly all CPU on tracing > through an enormous array each time it collects the tiny heap. That's true. Large objects (larger than 4k) aren't counted as live heap. It's not clear whether this is the right or wrong thing to do: the large objects aren't copied during GC, but they may be traced (eg. a large array of pointers). Furthermore, the live data strictly speaking should include the stack for each running thread (it doesn't currently). It's unlikely that the GC stats could be skewed by this: you'd need a huge array with all elements pointing to the same object. > I think rts.ps mentioned the possibility of using page fault stats to > automatically tune sizing. In some cases the user may already have a > good estimate of available real memory, and find it convenient to specify > a size (between the limits) which should be exceeded only when really > necessary. I'm not sure whether you'd want to set this by hand or have the RTS deal with it automatically, although I suspect the latter will give better results. The amount of free real memory in the system will likely fluctuate quite a bit, possibly during the run of the program itself. The downside of letting the RTS decide how much memory to use would be that it would start paging before it detected the fact and reduced memory consumption. Better OS support would help. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: +RTS -K in ghc-4
"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 :-) -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: +RTS -K in ghc-4
[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 > > According to 4-00-notes.vsgml, the latter -K4 means that the task > is performed within 4 bytes of heap+stack space. Well, actually the 4 bytes will be rounded up to the nearest "block size", ie. 4k. > This might happen, maybe, for sum [1..1000], but for the real > examples, it is somehow suspicious. > Could anybody tell, what does -K4 mean in time ./run +RTS -K4 > in ghc-4? > The whole test was to see, how the small space slows down the > performance. And it appears it does not value any :-) The maximum stack size shouldn't affect performance at all. The *minimum* stack size (i.e. the -k RTS option) will affect performance, as setting it too small will mean the stack may have to be copied several times. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: Further newbie compilation problems with GHC 4.00
Andrew Cheadle <[EMAIL PROTECTED]> writes: > [compilation output] > > > > ==fptools== make all -r; > in /a/hex/export32/bitbucket/amc4/development/fptools/ghc/lib/std > > > rm -f PrelBase.o ; if [ ! -d PrelBase ]; then mkdir PrelBase; else find > PrelBase -name '*.o' -print | xargs rm -f __rm_food ; fi ; > ../../../ghc/driver/ghc -recomp -cpp -fglasgow-exts -fvia-C -Rghc-timing > -O -split-objs -odir PrelBase -H10m -c PrelBase.lhs -o PrelBase.o > -osuf o > > PrelBase.lhs:18: Could not find valid interface file `PrelErr' > > PrelBase.lhs:18: Module `PrelErr' does not export `error' > > PrelBase.lhs:19: Could not find valid interface file `PrelGHC' This is on a fairly recent Linux installation w/ glibc, right? I had the same problem when I tried to compile 4.00 on one of the RedHat 5 boxes at Glasgow, but didn't get a chance to look into it. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: GHC 4.00 "Funny global thing?"
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?: cmUg_btm: This means you've got a pretty complex bit of code that needed a bitmap with more than 32 entries to describe a stack frame. Cool :-) > Resolve.hi and Resolve.o are generated. Can the "Funny global > thing?" message be ignored? (It does not crash the compiler.) Yep, the warning can be ignored. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: bootstrapping ghc on AIX
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.S). > I also tried to compile with USE_MINIINTERPRETER set to 1, but this > led to having to set INTERPRETER_ONLY to 1 as well, > otherwise Hugs_CONSTR_entry would be undefined. I asume that > "INTERPRETER_ONLY" means no compiler ? This is because I haven't done a powerpc of the new RTS yet. You've spotted the bits that are missing - mostly these can be filled in by looking at the relevant bits in the old RTS (from 3.02). > In case I'm not missing code and I have to write it myself, if > I don't use native code generation, can I do: > > #ifdef powerpc_TARGET_ARCH > > StgThreadReturnCode > StgRun(StgFunPtr f) { > f(); > return (StgThreadReturnCode)R1.i; > } > > #endif You need some hackery to save/restore callee-saves registers around the call to 'f'. The following is a complete guess, based on the old RTS code: StgThreadReturnCode StgRun(StgFunPtr f) { StgChar space[RESERVED_C_STACK_BYTES+6*sizeof(double)+19*sizeof(long)]; __asm__ volatile ("stm 13,-176(1)\n" "\tstfd 14,-200(1)\n" "\tstfd 15,-208(1)\n" "\tstfd 16,-216(1)\n" "\tstfd 17,-224(1)\n" "\tstfd 18,-232(1)\n" "\tstfd 19,-240(1)\n" : : "I" (RESERVED_C_STACK_BYTES+16) : "1" ); f(); __asm__ volatile (".align 3\n" ".globl " STG_RETURN "\n" STG_RETURN ":\n" "\tlm 13,-176(1)\n" "\tlfd 14,-200(1)\n" "\tlfd 15,-208(1)\n" "\tlfd 16,-216(1)\n" "\tlfd 17,-224(1)\n" "\tlfd 18,-232(1)\n" "\tlfd 19,-240(1)\n" : : "I" (RESERVED_C_STACK_BYTES+16) : "1" ); return (StgThreadReturnCode)R1.i; } > And for the "JMP_": > > #if powerpc_TARGET_ARCH > > #define JMP_(cont) \ > { \ > goto (void *)(cont); \ > } > > #endif powerpc_TARGET_ARCH Yep, this *should* work. > I don't know what to do about StgReturn in ghc/rts/StgRun.S, > judging from the ifdef, the StgReturn is only valid for 386 > architectures, so where is it defined on a sparc or an alpha ? You don't need to worry about StgRun.S (the glue code is *either* defined in StgRun.S or StgCRun.c, depending on whether you feel like writing it in assembler or C...) A small warning: the assembly manger (in ghc/driver/ghc-asm.lprl) may need a bit of tweaking for powerpc. Thanks for giving this a go... it shouldn't be too much work to get it all working. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: relocate_TSO
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 help is greatly appreciated. I would really love to see > GHC 4.00 in action ;-). Don't worry, I haven't forgotten you :-) Unfortunately, it'll be at least a week (and probably longer) before I can look into this. I'm really stumped as to why this would fail on Solaris (it is a Sparc, right?) and not on x86. If you have GHC sources on line, you could try building a debugging RTS (add -optC-DDEBUG -optC-g to RtsCcOpts in build.mk) and running gdb on the binary. Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key
Re: relocate_TSO
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:basicTypes:types:hsSyn:prelude:rename:typecheck:deSugar:coreSyn:specialise:simplCore:stranal:stgSyn:simplStg:codeGen:absCSyn:main:reader:profiling:parser:nativeGen > -recomp -Onot -H30m -fno-warn-incomplete-patterns -c rename/ParseIface.hs -o >rename/ParseIface.o -osuf o >GHC's heap exhausted; >while trying to allocate 0 bytes in a 65536-byte heap; These numbers are, of course, bogus. Part of the problem is that the new storage manager doesn't know how large a chunk the program was trying to allocate when it failed. This will be fixed at some point. And to get around the bootstrapping problem, try gmake EXTRA_HC_OPTS=-dcore-lint (the -dcore-lint option alleviates a space leak in the compiler. Sigh). Or this, to increase the heap size: gmake EXTRA_HC_OPTS=-optCrts-M128m > More seriously, today's CVS snapshot misses the distrib directory, but > simply copying an older one seems to work. Weird. I'll look into it as soon as I'm properly back online (a week or so). Cheers, Simon -- Simon Marlow [EMAIL PROTECTED] University of Glasgow http://www.dcs.gla.ac.uk/~simonm/ finger for PGP public key