- 26 Nov, 2001 4 commits
-
-
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
-
chak authored
Added a new section that describes how GHC defines its hardwired knowledge about primitives and special prelude definitions.
-
- 25 Nov, 2001 3 commits
-
-
sof authored
Tidyup - only declare&use half-a-dozen prof-only global variables when PROFILING.
-
sof authored
Retainer/LDV changes. The recent prof-related commit forgot to include RtsFlags.h, methinks. But, modulo trivia, I'm reasonably sure that this commit mirrors whatever mods that unchecked-in file contains.
-
sof authored
extend the scope of the doNothing() macro; can now be used in Stg headers
-
- 23 Nov, 2001 12 commits
-
-
simonpj authored
Put spaces round %, in preparation for splittable name supplies
-
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.
-
simonmar authored
Fix compilation problems with Stats.c in the !DEBUG case.
-
- 22 Nov, 2001 5 commits
-
-
simonmar authored
Omit GC and SYSTEM from the cost centre summary at the top of the profile.
-
simonmar authored
Add rts_getThreadId to the Linker's built in symbol table
-
simonmar authored
Retainer Profiling / Lag-drag-void profiling. This is mostly work by Sungwoo Park, who spent a summer internship at MSR Cambridge this year implementing these two types of heap profiling in GHC. Relative to Sungwoo's original work, I've made some improvements to the code: - it's now possible to apply constraints to retainer and LDV profiles in the same way as we do for other types of heap profile (eg. +RTS -hc{foo,bar} -hR -RTS gives you a retainer profiling considering only closures with cost centres 'foo' and 'bar'). - the heap-profile timer implementation is cleaned up. - heap profiling no longer has to be run in a two-space heap. - general cleanup of the code and application of the SDM C coding style guidelines. Profiling will be a little slower and require more space than before, mainly because closures have an extra header word to support either retainer profiling or LDV profiling (you can't do both at the same time). We've used the new profiling tools on GHC itself, with moderate success. Fixes for some space leaks in GHC to follow...
-
simonpj authored
Inlining pragma buglet
-
simonmar authored
Update this document. Some of the implementation problems can be solved in a cleaner way, and the document was confused about the problems caused by slop in the heap (it's only a problem when traversing the dead heap, not the live heap).
-
- 21 Nov, 2001 5 commits
-
-
sof authored
initialize_virtual_timer: Robustified win32 version; don't assume that the minimal resolution is one millisec, consult the underlying impl via timeGetDevCaps().
-
sof authored
StablePtr indexes/counts are no longer weighted (i.e., sync wrt Stable.{c,h} changes)
-
sof authored
#ifdef protect generated config.h file.
-
simonmar authored
Turn the weighted reference count in a StablePtr into a simple counter in the stable ptr table. We never made use of the weighted count, and it caused problems when making many StablePtrs to the same object. In the future we could remove the reference counting altogether and just make a new StablePtr each time, rather than attempting to use an existing one. This would save on the hash table lookup at creation time.
-
sof authored
Have prototypes and implementation of prel_PrelHandle_{write,read}() match up with the stated Haskell FFI type in PrelHandle.hs, i.e., the size parameter is a CInt, not an Int.
-
- 20 Nov, 2001 4 commits
-
-
sof authored
getTimes (win32): Win9x OSes don't provide per-process timing data, so GetProcessTimes() doesn't do anything interesting. So, resort to using system-time instead to measure user/process time iff running under Win9x. (the precision is not as good, deltas were ~6 millisecs when testing on a Win98 box, but it's better than nothing). This change should make profiling on Win9x boxes finally work.
-
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.
-
simonmar authored
Print to stdout instead of stderr. I'm pretty ambivalent about this, but Sungwoo Park made the changes as part of his retainer profiling work so he must have had a good reason for it at the time...
-
simonpj authored
Add constant-folding rules for Float# and Double#
-
- 19 Nov, 2001 5 commits
-
-
sof authored
If the configure script determined that the build-tree version of happy is to be used, descend into happy/ and build it, if needs be.
-
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.
-
- 18 Nov, 2001 1 commit
-
-
chak authored
Added a new section that covers lexing and parsing.
-
- 16 Nov, 2001 1 commit
-
-
sof authored
if IS_CBITS_LIB is YES: Extend SRC_HS2HS_OPTS in the same way that SRC_CC_OPTS is
-