- 27 Nov, 2001 3 commits
- 26 Nov, 2001 6 commits
-
-
simonpj authored
Complete previous tcAddImportedIdInfo commit
-
simonpj authored
Improve error reporting
-
simonpj authored
Comments only
-
simonpj authored
-------------------------------------- Finally get rid of tcAddImportedIdInfo -------------------------------------- TcEnv.tcAddImportedIdInfo is a notorious source of space leaks. Simon M got rid of the need for it on default methods. This commit gets rid of the need for it for dictionary function Ids, and finally nukes the beast altogether. Hurrah! The change really involves putting tcInterfaceSigs *before* tcInstDecls1, so that any imported DFunIds are in the typechecker's environment before we get to tcInstDecls.
-
simonpj authored
Add missing files for Rank-N commit
-
simonpj authored
---------------------- Implement Rank-N types ---------------------- This commit implements the full glory of Rank-N types, using the Odersky/Laufer approach described in their paper "Putting type annotations to work" In fact, I've had to adapt their approach to deal with the full glory of Haskell (including pattern matching, and the scoped-type-variable extension). However, the result is: * There is no restriction to rank-2 types. You can nest forall's as deep as you like in a type. For example, you can write a type like p :: ((forall a. Eq a => a->a) -> Int) -> Int This is a rank-3 type, illegal in GHC 5.02 * When matching types, GHC uses the cunning Odersky/Laufer coercion rules. For example, suppose we have q :: (forall c. Ord c => c->c) -> Int Then, is this well typed? x :: Int x = p q Yes, it is, but GHC has to generate the right coercion. Here's what it looks like with all the big lambdas and dictionaries put in: x = p (\ f :: (forall a. Eq a => a->a) -> q (/\c \d::Ord c -> f c (eqFromOrd d))) where eqFromOrd selects the Eq superclass dictionary from the Ord dicationary: eqFromOrd :: Ord a -> Eq a * You can use polymorphic types in pattern type signatures. For example: f (g :: forall a. a->a) = (g 'c', g True) (Previously, pattern type signatures had to be monotypes.) * The basic rule for using rank-N types is that you must specify a type signature for every binder that you want to have a type scheme (as opposed to a plain monotype) as its type. However, you don't need to give the type signature on the binder (as I did above in the defn for f). You can give it in a separate type signature, thus: f :: (forall a. a->a) -> (Char,Bool) f g = (g 'c', g True) GHC will push the external type signature inwards, and use that information to decorate the binders as it comes across them. I don't have a *precise* specification of this process, but I think it is obvious enough in practice. * In a type synonym you can use rank-N types too. For example, you can write type IdFun = forall a. a->a f :: IdFun -> (Char,Bool) f g = (g 'c', g True) As always, type synonyms must always occur saturated; GHC expands them before it does anything else. (Still, GHC goes to some trouble to keep them unexpanded in error message.) The main plan is as before. The main typechecker for expressions, tcExpr, takes an "expected type" as its argument. This greatly improves error messages. The new feature is that when this "expected type" (going down) meets an "actual type" (coming up) we use the new subsumption function TcUnify.tcSub which checks that the actual type can be coerced into the expected type (and produces a coercion function to demonstrate). The main new chunk of code is TcUnify.tcSub. The unifier itself is unchanged, but it has moved from TcMType into TcUnify. Also checkSigTyVars has moved from TcMonoType into TcUnify. Result: the new module, TcUnify, contains all stuff relevant to subsumption and unification. Unfortunately, there is now an inevitable loop between TcUnify and TcSimplify, but that's just too bad (a simple TcUnify.hi-boot file). All of this doesn't come entirely for free. Here's the typechecker line count (INCLUDING comments) Before 16,551 After 17,116
-
- 23 Nov, 2001 10 commits
-
-
simonmar authored
unbreak tcModule.
-
simonmar authored
Use (DefMeth Name) rather than (DefMeth Id) in ClassOpItem. This not only eliminates a space leak, because Names generally hold on to much less stuff than Ids, but also turns out to be a minor cleanup.
-
simonmar authored
Replace a lazy pattern match in tcGetInstLoc with a strict one (fixes a space leak).
-
simonmar authored
Adorn various constructor fields with strictness annotations - this fixes at least one space leak, in the mi_usages field of a ModIface.
-
simonmar authored
Collect up _scc_ expressions on the right hand side of a closure definition and attach them directly to the closure using PushCC-type cost centres, so that the allocation of the closure gets attributed to the right place.
-
simonmar authored
Fix a long-standing bug in the cost attribution of cost-center stacks. The problem case is this: let z = _scc_ "z" f x in ... z ... previously we were attributing the cost of allocating the closure 'z' to the enclosing cost center stack (CCCS), when it should really be attributed to "z":CCCS. The effects are particularly visible with retainer profiling, because the closure retaining 'f' and 'x' would show up with the wrong CCS attached. To fix this, we need a new form of CCS representation internally: 'PushCC CostCentre CostCentreStack' which subsumes (and therefore replaces) SingletonCCS. SingletonCCS is now represented by 'PushCC cc NoCCS'. The CCS argument to SET_HDR may now be an arbitrary expression, such as PushCostCentre(CCCS,foo_cc), as may be the argument to CCS_ALLOC(). So we combine SET_HDR and CCS_ALLOC into a single macro, SET_HDR_, to avoid repeated calls to PushCostCentre().
-
simonmar authored
Call LDV_ENTER() on entry to a constructor in profiling mode.
-
simonmar authored
Call LDV_ENTER() on entry to a thunk or function in profiling mode.
-
simonmar authored
Add ldvEnter :: Code for LDV profiling: it records that the closure pointed to by R1 has just been entered.
-
simonmar authored
We don't need to consider Hp as a volatile register across C calls; it is already saved by the CALLER_SAVES_SYSTEM macro.
-
- 22 Nov, 2001 1 commit
-
-
simonpj authored
Inlining pragma buglet
-
- 20 Nov, 2001 1 commit
-
-
sof authored
Nuke #include of MachDeps.h - nothing in there that cannot be (better) gotten from the in-tree config.h This is the only (last?) use of MachDeps.h, so if anyone won't argue for its continued existence, I'll nuke it sometime soon.
-
- 19 Nov, 2001 4 commits
-
-
sof authored
- change the interpretation of FPTOOLS_TOP_ABS, it is now the UNIXy path. For Win32, it is of the form <drive>:<path> where '/' is the directory separator. Prior to this commit, the directory separator was '\'. - for the (only) place we need to have a platform-native representation of FPTOOLS_TOP_ABS, use FPTOOLS_TOP_ABS_PLATFORM.
-
simonpj authored
Tidy up imports
-
simonpj authored
Improve error msg
-
simonpj authored
-------------------------------------- Yet another cut at the DmdAnal domains -------------------------------------- This version of the domain for demand analysis was developed in discussion with Peter Sestoft, so I think it might at last be more or less right! Our idea is mentally to separate strictness analysis from absence and boxity analysis Then we combine them back into a single domain. The latter is all you see in the compiler (the Demand type, as before) but we understand it better now.
-
- 16 Nov, 2001 1 commit
-
-
simonpj authored
--------------------------------------- Add continuation splitting to Simplify --------------------------------------- When the simplifier finds a 'case', it calls mkDupableAlt to make the "continuation" (that is, the context of the case expression) duplicatable, so that it can push it into the case branches. This is crucial for the case-of-case transformation. But it turns out that it's a bad idea to do that when the context is "I'm the argument of a strict function". Consider f (case x of { True -> False; False -> True }) arg2 where f is a strict function. Then we *could* (and were) transforming to let $j a = f a arg2 in case x of { True -> $j False; False -> $j True } But this is in general a terribly bad thing to do. See the example in comments with Simplify.mkDupableCont.
-
- 12 Nov, 2001 1 commit
-
-
simonpj authored
Remove pprTrace
-
- 09 Nov, 2001 6 commits
-
-
sof authored
GhcCanonVersion: leave out GhcPatchLevel, causes problems when the GhcPatchLevel isn't a patchlevel but a date.
-
sof authored
lookupInstEnv: "#ifdef DEBUG"-protect trace code that got included in prev. commit. (I'm guessing it either should be removed or moved into the ASSERT, but I'll let the original committer decide which).
-
sof authored
* Moved CANON_HC_VERSION out of ghc/compiler/Makefile and into mk/config.mk.in (and renamed it as GhcCanonVersion). * Have ghc/driver/Makefile use it; cheaper and more robust than the version testing it was already doing.
-
sof authored
Optimised defn of CANON_HC_VERSION, synthesise it from config.mk info, not via an expensive $(shell ...) call.
-
sof authored
Use -fvia-C when compiling rename/ParseIface.hs and parser/Parser.hs - Int16 primops aren't supported by the NCG on all plats.
-
simonpj authored
--------------------------------------- Fix an obscure overlapping-instance bug --------------------------------------- MERGE TO STABLE BRANCH When searching for instances, we used bale out if the type we seek could be instantiated to match the instance (because it might be so instantiated later, in which case we don't want to miss the opportunity). The bug was that we used *matching* whereas we should use *unification*. Comments in the file InstEnv.
-
- 08 Nov, 2001 6 commits
-
-
sof authored
gen_Eq_binds: when comparing constructor tags, emit just a == b = case con2tag_Foo# a of a# -> case con2tag_Foo# b of b# -> a# PrelGHC.==# b# and not a == b = case con2tag_Foo# a of a# -> case con2tag_Foo# b of b# -> if a# PrelGHC.==# b# then PrelBase.True else PrelBase.False (Not that this wouldn't get simplified, but still).
-
sof authored
rnHsForeignDecl: 'foreign import's (incl 'f.e.d's) _define_ local toplevel names, so better use RnEnv.lookupTopBndrRn and not RnEnv.lookupOccRn to resolve the name. As was, declaring ForeignImports with the same name as an imported entity wasn't permitted.
-
sof authored
gencode: for completeness sake only, handle CCallTypedefs
-
sof authored
ghc-inplace: single-quote -B option to avoid de-escaping those b-slashes
-
simonmar authored
Updates to the native code generator following the changes to fix the large block allocation bug, and changes to use the new function-address cache in the register table to reduce code size. Also: I changed the pretty-printing machinery for assembly code to use Pretty rather than Outputable, since we don't make use of the styles and it should improve performance. Perhaps the same should be done for abstract C.
-
simonmar authored
Remove the heap-check-size panic, following the RTS fixes for this problem.
-
- 07 Nov, 2001 1 commit
-
-
sof authored
When generating dependencies, look for both source files _and_ interface files. If STABLE is still a branch with a future, I'd encourage merging.
-