- 17 Dec, 2014 13 commits
-
-
Simon Peyton Jones authored
See Note [Disgusting computation of CafRefs] in TidyPgm. Also affects CoreUtils.rhsIsStatic. The real solution here is to compute CAF and arity information from the STG-program, and feed it back to tidied program for the interface file and later GHCi clients. A battle for another day. But at least this commit reduces the number of gratuitous CAFs, and hence SRT entries. And kills off a batch of ASSERT failures.
-
Simon Peyton Jones authored
There were two related bugs here Trac #9426 We must increment the ic_mod_index field of the InteractiveContext if we have new instances, because we maek DFunIds that should be distinct from previous ones. Previously we were only incrementing when defining new user-visible Ids. The main change is in HscTypes.extendInteractiveContext, which now alwyas bumps the ic_mod_index. I also added a specialised extendInteractiveContextWithIds for the case where we are *only* adding new user-visible Ids. Trac #9424 In HscMain.hscDeclsWithLocations we were failing to use the *tidied* ClsInsts; but the un-tidied ones are LocalIds which causes a later ASSERT error. On the way I realised that, to behave consistently, the tcg_insts and tcg_fam_insts field of TcGblEnv should really only contain instances from the current GHCi command, not all the ones to date. That in turn meant I had to move the code for deleting replacement instances from addLocalInst, addLocalFamInst to HscTypes.extendInteractiveContext
-
Simon Peyton Jones authored
See Note [Checking for INLINE loop breakers]
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
Previously we were capturing the *entire environment* when moving under a 'proc', for the newArrowScope/escapeArrowScope thing. But that a blunderbuss, and in any case isn't right (the untouchable-type-varaible invariant gets invalidated). So I fixed it to be much more refined: just the LocalRdrEnv and constraints are captured. I think this is right; but if not we should just add more fields to ArrowCtxt, not return to the blunderbuss. This patch fixes the ASSERT failure in Trac #5267
-
Gabor Greif authored
with GHC HEAD. Reworked using deriving instance.
-
Gabor Greif authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
This pulls in the fix for the broken `@since`-rendering
-
Peter Wortmann authored
This tells debuggers such as GDB how to "unwind" a program state, which allows them to walk the stack up. Notes: * The code is quite general, perhaps unnecessarily so. Unless we get more unwind information, only the first case of pprSetUnwind will get used - and pprUnwindExpr and pprUndefUnwind will never be called. It just so happens that this is a point where we can get a lot of features cheaply, even if we don't use them. * When determining what location to show for a return address, most debuggers check the map for "rip-1", assuming that's where the "call" instruction is. For tables-next-to-code, that happens to always be the end of an info table. We therefore cheat a bit here by shifting .debug_frame information so it covers the end of the info table, as well as generating a .loc directive for the info table data. Debuggers will still show the wrong label for the return address, though. Haven't found a way around that one yet. (From Phabricator D396)
-
Peter Wortmann authored
This is where we actually make GHC emit DWARF code. The info section contains all the general meta information bits as well as an entry for every block of native code. Notes: * We need quite a few new labels in order to properly address starts and ends of blocks. * Thanks to Nathan Howell for taking the iniative to get our own Haskell language ID for DWARF! (From Phabricator D396)
-
Peter Wortmann authored
This generates DWARF, albeit indirectly using the assembler. This is the easiest (and, apparently, quite standard) method of generating the .debug_line DWARF section. Notes: * Note we have to make sure that .file directives appear correctly before the respective .loc. Right now we ppr them manually, which makes them absent from dumps. Fixing this would require .file to become a native instruction. * We have to pass a lot of things around the native code generator. I know Ian did quite a bit of refactoring already, but having one common monad could *really* simplify things here... * To support SplitObjcs, we need to emit/reset all DWARF data at every split. We use the occassion to move split marker generation to cmmNativeGenStream as well, so debug data extraction doesn't have to choke on it. (From Phabricator D396)
-
- 16 Dec, 2014 21 commits
-
-
Sergei Trofimovich authored
Summary: It exempts us from 11 reduce/reduce conflicts and 12 shift/reduce conflicts. Signed-off-by:
Sergei Trofimovich <siarheit@google.com> Reviewers: simonpj, mikeizbicki, austin, simonmar Reviewed By: simonmar Subscribers: carter, thomie Differential Revision: https://phabricator.haskell.org/D571
-
Herbert Valerio Riedel authored
-
Peter Wortmann authored
Adds a test way for debug (-g -dannot-lint) as well as a test covering basic source tick functionality. The debug way fails for a number of test cases because of annotation linting: Tracing simplification (e.g. rule firings) will see duplicated output, and sometimes expression matching might take so long that the test case timeouts. We blacklist these tests. (From Phabricator D169)
-
Peter Wortmann authored
The purpose of the Debug module is to collect all required information to generate debug information (DWARF etc.) in the back-ends. Our main data structure is the "debug block", which carries all information we have about a block of code that is going to get produced. Notes: * Debug blocks are arranged into a tree according to tick scopes. This makes it easier to reason about inheritance rules. Note however that tick scopes are not guaranteed to form a tree, which requires us to "copy" ticks to not lose them. * This is also where we decide what source location we regard as representing a code block the "best". The heuristic is basically that we want the most specific source reference that comes from the same file we are currently compiling. This seems to be the most useful choice in my experience. * We are careful to not be too lazy so we don't end up breaking streaming. Debug data will be kept alive until the end of codegen, after all. * We change native assembler dumps to happen right away for every Cmm group. This simplifies the code somewhat and is consistent with how pretty much all of GHC handles dumps with respect to streamed code. (From Phabricator D169)
-
Peter Wortmann authored
Unwind information allows the debugger to discover more information about a program state, by allowing it to "reconstruct" other states of the program. In practice, this means that we explain to the debugger how to unravel stack frames, which comes down mostly to explaining how to find their Sp and Ip register values. * We declare yet another new constructor for CmmNode - and this time there's actually little choice, as unwind information can and will change mid-block. We don't actually make use of these capabilities, and back-end support would be tricky (generate new labels?), but it feels like the right way to do it. * Even though we only use it for Sp so far, we allow CmmUnwind to specify unwind information for any register. This is pretty cheap and could come in useful in future. * We allow full CmmExpr expressions for specifying unwind values. The advantage here is that we don't have to make up new syntax, and can e.g. use the WDS macro directly. On the other hand, the back-end will now have to simplify the expression until it can sensibly be converted into DWARF byte code - a process which might fail, yielding NCG panics. On the other hand, when you're writing Cmm by hand you really ought to know what you're doing. (From Phabricator D169)
-
Peter Wortmann authored
This patch solves the scoping problem of CmmTick nodes: If we just put CmmTicks into blocks we have no idea what exactly they are meant to cover. Here we introduce tick scopes, which allow us to create sub-scopes and merged scopes easily. Notes: * Given that the code often passes Cmm around "head-less", we have to make sure that its intended scope does not get lost. To keep the amount of passing-around to a minimum we define a CmmAGraphScoped type synonym here that just bundles the scope with a portion of Cmm to be assembled later. * We introduce new scopes at somewhat random places, aligning with getCode calls. This works surprisingly well, but we might have to add new scopes into the mix later on if we find things too be too coarse-grained. (From Phabricator D169)
-
Peter Wortmann authored
This patch adds CmmTick nodes to Cmm code. This is relatively straight-forward, but also not very useful, as many blocks will simply end up with no annotations whatosever. Notes: * We use this design over, say, putting ticks into the entry node of all blocks, as it seems to work better alongside existing optimisations. Now granted, the reason for this is that currently GHC's main Cmm optimisations seem to mainly reorganize and merge code, so this might change in the future. * We have the Cmm parser generate a few source notes as well. This is relatively easy to do - worst part is that it complicates the CmmParse implementation a bit. (From Phabricator D169)
-
Peter Wortmann authored
They would be unneeded at minimum. Not completely sure this is the right place to do this. (From Phabricator D169)
-
Peter Wortmann authored
This is basically just about continuing maintaining source notes after the Core stage. Unfortunately, this is more involved as it might seem, as there are more restrictions on where ticks are allowed to show up. Notes: * We replace the StgTick / StgSCC constructors with a unified StgTick that can carry any tickish. * For handling constructor or lambda applications, we generally float ticks out. * Note that thanks to the NonLam placement, we know that source notes can never appear on lambdas. This means that as long as we are careful to always use mkTick, we will never violate CorePrep invariants. * This is however not automatically true for eta expansion, which needs to somewhat awkwardly strip, then re-tick the expression in question. * Where CorePrep floats out lets, we make sure to wrap them in the same spirit as FloatOut. * Detecting selector thunks becomes a bit more involved, as we can run into ticks at multiple points. (From Phabricator D169)
-
Peter Wortmann authored
This adds a way by which we can make sure that the Core passes treat annotations right: We run them twice and compare the results. The main problem here is that Core equivalence is awkward: We do not want the comparison to care about the order of, say, top-level or recursive bindings. This is important even if GHC generally generates the bindings in the right order - after all, if something goes wrong we don't want linting to dump out the whole program as the offense. So instead we do some heuristic matching - first greedily match everything that's easy, then match the rest by label order. This should work as long as GHC generates the labels in roughly the same order for both pass runs. In practice it seems to work alright. We also check that IdInfos match, as this might cause hard-to-spot bugs down the line (I had at least one bug because unfolding guidance didn't match!). We especially check unfoldings up until the point where it might get us into an infinite loop. (From Phabricator D169)
-
Peter Wortmann authored
This allows having, say, HPC ticks, automatic cost centres and source notes active at the same time. We especially take care to un-tangle the infrastructure involved in generating them. (From Phabricator D169)
-
Peter Wortmann authored
This patch introduces "SourceNote" tickishs that link Core to the source code that generated it. The idea is to retain these source code links throughout code transformations so we can eventually relate object code all the way back to the original source (which we can, say, encode as DWARF information to allow debugging). We generate these SourceNotes like other tickshs in the desugaring phase. The activating command line flag is "-g", consistent with the flag other compilers use to decide DWARF generation. Keeping ticks from getting into the way of Core transformations is tricky, but doable. The changes in this patch produce identical Core in all cases I tested -- which at this point is GHC, all libraries and nofib. Also note that this pass creates *lots* of tick nodes, which we reduce somewhat by removing duplicated and overlapping source ticks. This will still cause significant Tick "clumps" - a possible future optimization could be to make Tick carry a list of Tickishs instead of one at a time. (From Phabricator D169)
-
Joachim Breitner authored
cf. a4ec0c92 and 289e52f8
-
Herbert Valerio Riedel authored
Starting with Haddock 2.16 there's a new built-in support for since-annotations Note: This exposes a bug in the `@since` implementation (see e.g. `Data.Bits`)
-
Herbert Valerio Riedel authored
-
Joachim Breitner authored
to avoid a build failure with T5681(optllvm). According to Ben Gamari, llvm-3.4 is known to be not working with GHC HEAD.
-
Herbert Valerio Riedel authored
The actual gitlink update got lost in 0c9c2d89
-
Gabor Greif authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
-
Herbert Valerio Riedel authored
-
- 15 Dec, 2014 6 commits
-
-
Simon Marlow authored
-
Simon Marlow authored
-
Simon Marlow authored
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
THe documentation in 7.9.4 of promoted list and tuple types was misleading, which led to Trac #9882. This patch makes explicit that only type-level with two or more elements can have the quote omitted.
-