- 14 Sep, 2001 4 commits
-
-
simonpj authored
Add comments
-
simonpj authored
-------------------------- Cleanup in DataCon -------------------------- DO NOT merge with stable The dataConRepStrictness call used to reuturn a [Demand], but that's a bit misleading. In particular, consider a strict constructor data Foo = MkFoo ![Int] Then the wrapper MkFoo is strict, but the worker $wMkFoo is not. MkFoo x = case x of { DEFAULT -> $wMkFoo x } Nevertheless, when we pattern-match on $wMkFoo we will surely find an evaluated component to the data structure, and that is what dataConRepStrictness reports, and that's how it is used in Simplify. Solution: make dataConRepStrictness return [StrictnessMark] not [Demand]. A small matter really.
-
simonmar authored
oops: hPutStr wasn't flushing a line-buffered handle properly at the end of a line. MERGE TO STABLE
-
sewardj authored
Make rotate fns work properly when rotate count is a multiple of the word size. This fixes sparc failures in ghc-regress/numeric/should_run/arith011. Also fix some copy-and-paste-o-s.Killed by signal 2. MERGE TO STABLE
-
- 13 Sep, 2001 2 commits
- 12 Sep, 2001 8 commits
-
-
sewardj authored
merge (ghc-5-02-branch --> HEAD): Bugfix: there was an implicit assumption that the list of slots passed to freeStackSlots was already sorted, whereas in fact this wasn't the case for at least one call. Now we explicitly sort the list in freeStackSlots, removing the hidden assumption. The symptoms of this bug include crashes (perhaps the "AsmCodeGen" crash), and a tendency to grow the stack a lot when let-no-escapes are involved (because the bug caused fragmentation of the stack free list, so we weren't re-using free slots properly). 1.17.2.1 +3 -2 fptools/ghc/compiler/codeGen/CgStackery.lhs ASSERT that the list of stack slots we calculate in buildLivenessMask is sorted, because we rely on that property later. 1.38.2.1 +5 -6 fptools/ghc/compiler/codeGen/CgBindery.lhs
-
sewardj authored
Redo half-arsed hacks to do with BSS symbols on ELF. Hopefully get it right this time. MERGE TO STABLE
-
rrt authored
Do the ifdefery properly so it works on Unix.
-
rrt authored
Updated to new directory structure (no extra-bin), and with all the right binaries in bin.
-
rrt authored
Make hsc2hs find template-hsc.h on Windows. This involves putting Main.hs through cpp; to avoid the string gap problem preprocessing __GLASGOW_HASKELL__ into its value inside strings, make judicious use of ++ (hope that's OK, Marcin; there seemed very little point in putting it all in KludgedSystem this time).
-
qrczak authored
Fix comment.
-
qrczak authored
Fix creating HSstd.o.
-
qrczak authored
Don't exclude PrelMain.o from libHSstd.a.
-
- 11 Sep, 2001 3 commits
-
-
rje authored
hasktags is now built as part of the standard build process.
-
simonpj authored
-------------------------- Strictness of blockAsynch -------------------------- MERGE WITH STABLE BRANCH If we're going to supply strictness info for blockAsynchExceptions#, it should match its arity (as other State# transformers do).
-
simonpj authored
----------------------- More demand-info fixes ----------------------- MERGE WITH STABLE BRANCH There are a handful of functions in IdInfo that zap the demand-info stored in an Id. Alas, they were zapping the *old* demand-info not the new one. (The old one is still there for comparison purposes.) So we were getting some spurious warnings and (more seriously) potentially some incorrect strictness. Easily fixed though.
-
- 10 Sep, 2001 7 commits
-
-
simonmar authored
Sync the documentation with the extra-bin removal.
-
simonmar authored
oops, revert accidental commit
-
simonmar authored
good riddance
-
simonmar authored
Remove the "extra-bin" subdirectory from $(libexecdir), since there are too many assumptions in the tree that $(libexecdir) == $(libdir) (at the moment, binary dists are fairly well broken). Reuben has promised to track the change in the Windows distribution.
-
rje authored
Fixed a bug in TICKY_TICKY profiling. Previously, the TICK_ENT_DIRECT event was logged before the heap/stack check was done. As a result, if the check failed, the TICK_ENT_DIRECT event would be logged a second time, causing TICKY_TICKY to give innacurate numbers. This patch shouldn't have any affect on non-ticky compilation. Also changed the modified bit of code to use "do" notation, and so look a bit neater.
-
simonpj authored
Fix ungramatical error message
-
simonpj authored
----------------------------------- Fix a strictness bug in the simplifier ----------------------------------- This one has been there a long time, but hasn't bitten till now. We should never float a let that is marked "sure to be evaluated" out of a let. It shouldn't happen, and there was a warning to check, but the warning cried 'wolf' too often, so we have generally ignored it. But the wolf called for supper, when compiling spectral/expert with profiling on. The fix is simple too: * use exprIsValue not exprIsCheap as the test * move the warning, so it doesn't cry wolf Documentation with Simplify.simplRhs. On the way, I'm going to conmmit a change in the same module, which keeps unfolding info on lambda-bound variables. This improves the elimination of cases when the wrapper does the 'seq' -- then the worker gets to know that the arg is evaluated.
-
- 08 Sep, 2001 2 commits
-
-
ken authored
Make the binary distribution configure recognize alphaev56-dec-osf5. MERGE TO STABLE.
-
sof authored
Remove ugly special casing - if you want to turn off the default rule for GHCI_LIBRARY, set DONT_WANT_STD_GHCI_LIB_RULE to YES in your Makefile prior to including $(TOP)/mk/target.mk ghc/lib/std and hslibs/win32 both do this now on mingw32.
-
- 07 Sep, 2001 10 commits
-
-
simonpj authored
Make isStrictDmd give the right answer
-
simonpj authored
Make dmdFix not loop forever
-
sewardj authored
Fix compilation with -DDEBUG. MERGE TO STABLE
-
simonpj authored
Improve the error message for duplicate or invalid binders in a binding group. [Consequence: rnfail034 should not be an expected failure any more] MERGE WITH STABLE BRANCH
-
simonpj authored
---------------------------------------- Make dict funs and default methods into LocalIds only at their binding site ---------------------------------------- [part of 3 related commits] There's a long comment about this with MkId.mkDefaultMethodId, which I reproduce below. While I was at it, I renamed setIdNoDiscard to setIdLocalExported. Which is hardly an improvement, I'm afraid. This renaming touches Var.lhs, Id.lhs, SimplCore.lhs in a trivial way. --------------------- Dict funs and default methods are *not* ImplicitIds. Their definition involves user-written code, so we can't figure out their strictness etc based on fixed info, as we can for constructors and record selectors (say). We build them as GlobalIds, but when in the module where they are bound, we turn the Id at the *binding site* into an exported LocalId. This ensures that they are taken to account by free-variable finding and dependency analysis (e.g. CoreFVs.exprFreeVars). The simplifier will propagate the LocalId to all occurrence sites. Why shouldn't they be bound as GlobalIds? Because, in particular, if they are globals, the specialiser floats dict uses above their defns, which prevents good simplifications happening. Also the strictness analyser treats a occurrence of a GlobalId as imported and assumes it contains strictness in its IdInfo, which isn't true if the thing is bound in the same module as the occurrence. It's OK for dfuns to be LocalIds, because we form the instance-env to pass on to the next module (md_insts) in CoreTidy, afer tidying and globalising the top-level Ids. BUT make sure they are *exported* LocalIds (setIdLocalExported) so that they aren't discarded by the occurrence analyser.
-
simonpj authored
----------------------------------- Pin on accurate strictness info for record and dictionary selectors ----------------------------------- [part of 3 related commits] This fixes a long-standing infelicity. Sometimes selectors aren't inlined until after strictness analysis, so if we don't have decent strictness info on them we get bad strictness results. For record selectors, the unboxing-strict-fields stuff makes it hard to figurwe out the correct strictness, so we just invoke the demand analyser to work it out.
-
simonpj authored
------------------------ Fix the demand analyser ------------------------ A spiffy new domain for demands, and definitions for lub/both which are actually monotonic. Quite a bit of related jiggling around. One of the original motivations was to do with functions like: sum n [] = n sum n (x:xs) = sum (n+x) xs Even though n is returned boxed from the first case, we don't want to get strictness S(L)V -> T because that means we pass the box for n, and that is TERRIBLE. So the new version errs on the side of unboxing, more like the forwards analyser, and only passes the box if it is *definitely* needed, rather than if it *may* be needed.
-
simonpj authored
Omit unnecessary import
-
simonpj authored
------------------- Newtypes and ccalls [addendum] ------------------- MERGE WITH STABLE BRANCH I accidentally omitted these two wibbles from my previous commit. I've added PrelNames.unitTyConKey, and used it in TcType and DsCCall.
-
simonpj authored
------------------- Newtypes and ccalls ------------------- MERGE WITH STABLE BRANCH Yet another bit of newtype-squashing that hadn't been synced with reality. In desugaring ccalls, we can still see newtypes, if they are recursive, and we must generate appropriate coerces. Fixes a bug in cg011.
-
- 06 Sep, 2001 4 commits
-
-
ken authored
Fix the code to *really* do the following: On the Alpha we can only handle <= 4 integer arguments with foreign export dynamic. Following the example of the corresponding Sparc hack, we detect when we're being asked to do something we can't and refuse. MERGE TO STABLE BRANCH
-
apt authored
document -fext-core flag and set pointers to ext-core docs/tools (MERGE to STABLE pleeeeeease.)
-
simonpj authored
Import wibbles
-
sewardj authored
Change a couple more Int32s into CTimes, which they are really.
-