- 07 Dec, 2001 5 commits
-
-
sof authored
Track the removal of ReallyUnsafePtrEqualityOp + InterTo{Int,Word}64Op primops.
-
sewardj authored
Change the story on shifting primops: SllOp, SrlOp, ISllOp, ISraOp, ISrlOp. In the old primop story, these were implemented by C macros which checked that the shift amount did not exceed the word size, and if so returns a suitable value (0 or -1). This gives consistent, defined behaviour for any shift amount. However, these checks were not implemented on the NCG route, an inconsistency. New story: these primops do NOT check their args; they just do the shift. Shift values >= word size give undefined results. To reflect this, their Haskell names have been prefixed with 'unchecked'. The checks are now done on the Bits instances in the Prelude. This means all code generation routes are consistently checked, and hopefully the simplifier will remove the checks for literal shift amounts. I have tried to fix up the implementation for 64-bit platforms too, but not having one to hand, I don't know if it will work as-is.
-
sewardj authored
Comments only.
-
sof authored
mkExportAvails: computing the AvailEnv is rather delicate
-
sof authored
Tidyup - previous instance-decl commit fell a bit short: * RnEnv.lookupInstDeclBndr unceremoniously fell over when passed an out-of-scope class name. * the AvailEnv carried around didn't common up type/class info (i.e., AvailTCs), but rather type/class and method/label names, causing the renamer to (semi)randomly report instance methods as being out-of-scope in the presence of multiple imports for a module. * didn't support 'hiding' of class / method names (for the purposes of checking instance decls).
-
- 06 Dec, 2001 14 commits
-
-
simonmar authored
Make the Name field of a Var strict - it doesn't hurt performance (in fact it makes a tiny improvement) but it can help residency.
-
simonmar authored
Turn a lazy pattern match into a strict one in tidyIdBndr. This prevents us accidentally hanging onto stuff in the OccName field of a Name after tidying.
-
simonmar authored
- Fix THUNK_SELECTOR printing code - change some more stderrs into stdouts
-
sewardj authored
Make it compile -DDEBUG.
-
sewardj authored
Remove out-of-date ASSERT in deRefStablePtr_fast.
-
chak authored
Make prof package dependency more precise
-
sewardj authored
Add constructor CBytesPerWord to (the wildly-misnamed) CAddrMode, and use this in various places to remove word size dependencies in the C -> C simplification pass. Tart up the Stix constant folder a bit so as to be able to fold out the shift/mask literal expressions.
-
simonpj authored
-------------------------- Fix the instance-decl wart -------------------------- This commit implements the (proposed) H98 rule for resolving the class-method name in an instance decl. module M( C( op1, op2 ) ) where -- NB: op3 not exported class C a where op1, op2, op3 :: a -> a module N where import qualified M as P( C ) import qualified M as Q hiding( op2 ) instance P.C Int where op1 x = x -- op2, op3 both illegal here The point is that a) only methods that can be named are legal in the instance decl (so op2, op3 are not legal) b) but it doesn't matter *how* they can be named (in this case Q.op1 is in scope, though the class is called P.C) The AvailEnv carries the information about what's in scope, so we now have to carry it around in the monad, so that instance decl bindings can see it. Quite simple really. Same deal for export lists. E.g. module N( P.C( op1 ) ) where import qualified M as P( C ) import qualified M as Q hiding( op2 ) Actually this is what GHC has always implemented!
-
simonpj authored
Comments only
-
mbs authored
Established under cvs.
-
sewardj authored
Remove mention of PrimOpHelpers.h.
-
simonpj authored
Fix the simplIdInfo inconsistency Sigbjorn found
-
sof authored
package rts (mingw32): in installed mode, add gcc-lib/ to library_dirs, forcing it to be used by default. This allows other backend tools to be used (e.g., `dllwrap') without haphazardly mixing & matching (import) libs. MERGE TO STABLE.
-
sof authored
startupHaskell: if invoked more than once, do run initModules() each time, as there might be more than one 'root module'.
-
- 05 Dec, 2001 11 commits
-
-
sof authored
oops, changes not tested with a stage2 build
-
sewardj authored
-------------------------------------------- Translate out PrimOps at the AbstractC level -------------------------------------------- This is the first in what might be a series of changes intended to make GHC less dependent on its C back end. The main change is to translate PrimOps into vanilla abstract C inside the compiler, rather than having to duplicate that work in each code generation route. The main changes are: * A new type, MachOp, in compiler/absCSyn/MachOp.hs. A MachOp is a primitive operation which we can reasonably expect the native code generators to implement. The set is quite small and unlikely to change much, if at all. * Translations from PrimOps to MachOps, at the end of absCSyn/AbsCUtils. This should perhaps be moved to a different module, but it is hard to see how to do this without creating a circular dep between it and AbsCUtils. * The x86 insn selector has been updated to track these changes. The sparc insn selector remains to be done. As a result of this, it is possible to compile much more code via the NCG than before. Almost all the Prelude can be compiled with it. Currently it does not know how to do 64-bit code generation. Once this is fixed, the entire Prelude should be compilable that way. I also took the opportunity to clean up the NCG infrastructure. The old Stix data type has been split into StixStmt (statements) and StixExpr (now denoting values only). This removes a class of impossible constructions and clarifies the NCG. Still to do, in no particular order: * String and literal lifting, currently done in the NCG at the top of nativeGen/MachCode, should be done in the AbstractC flattener, for the benefit of all targets. * Further cleaning up of Stix assignments. * Remove word-size dependency from Abstract C. (should be easy). * Translate out MagicIds in the AbsC -> Stix translation, not in the Stix constant folder. (!) Testsuite failures caused by this: * memo001 - fails (segfaults) for some unknown reason now. * arith003 - wrong answer in gcdInt boundary cases. * arith011 - wrong answer for shifts >= word size. * cg044 - wrong answer for some FP boundary cases. These should be fixed, but I don't think they are mission-critical for anyone.
-
simonmar authored
Add -s flag to Happy if we have version 1.12+
-
sof authored
make it compile - i.e., use Subst.simplIdInfo in a manner consistent with the repo contents. (wouldn't surprise me if there's coreSyn/Subst.lhs change that hasn't been committed yet...)
-
simonpj authored
Preserve IdInfo for strict binders
-
simonmar authored
Make some record selections strict to reduce space leaks.
-
simonmar authored
unbreak inputReady().
-
simonmar authored
Add seqDemand, seqDemands, seqDmdType and seqStrictSig.
-
simonmar authored
- fix a space leak in the cg_env passed back from the code generator to CoreTidy that was keeping the result of CoreToStg alive through code generation. - some cost centre changes
-
sof authored
- new option, -keep-ilx-file, for stashing away ILX input. - restrict ILX-specific code/defs to only be visible iff ILX is #defined.
-
sof authored
reuse Panic.showGhcException
-
- 04 Dec, 2001 8 commits
-
-
sof authored
Enable the (already advertised) dependency generation options --exclude-module=<mod> and -x <mod>.
-
sof authored
genPipeLine: DoMkDll didn't have a stop_phase, causing any use of --mk-dll to fall over. MERGE TO STABLE.
-
simonmar authored
Omit the whole file, not just the exports, if DEBUG is off.
-
sewardj authored
Update to follow the __init_Foo -> __stginit_Foo change.
-
sof authored
minor tidyup - move CollectedCCs tysyn to CostCentre (from SCCFinal), and make use of it where that cost-centre info triple is being passed&returned.
-
sof authored
make it compile
-
keller authored
Sets the X11 C compiler and linker flags for package xlib correctly now
-
keller authored
added closing bracket at end of file
-
- 03 Dec, 2001 2 commits