- Sep 13, 2013
-
-
Iavor S. Diatchki authored
This patch implements some simple evaluation of type-level expressions featuring natural numbers. We can evaluate *concrete* expressions that use the built-in type families (+), (*), (^), and (<=?), declared in GHC.TypeLits. We can also do some type inference involving these functions. For example, if we encounter a constraint such as `(2 + x) ~ 5` we can infer that `x` must be 3. Note, however, this is used only to resolve unification variables (i.e., as a form of a constraint improvement) and not to generate new facts. This is similar to how functional dependencies work in GHC. The patch adds a new form of coercion, `AxiomRuleCo`, which makes use of a new form of axiom called `CoAxiomRule`. This is the form of evidence generate when we solve a constraint, such as `(1 + 2) ~ 3`. The patch also adds support for built-in type-families, by adding a new form of TyCon rhs: `BuiltInSynFamTyCon`. such built-in type-family constructors contain a record with functions that are used by the constraint solver to simplify and improve constraints involving the built-in function (see `TcInteract`). The record in defined in `FamInst`. The type constructors and rules for evaluating the type-level functions are in a new module called `TcTypeNats`.
-
- Sep 12, 2013
-
-
Jan Stolarek authored
This commit does two things: * Allows duplicating of global registers and literals by inlining them. Previously we would only inline global register or literal if it was used only once. * Changes method of determining conflicts between a node and an assignment. New method has two advantages. It relies on DefinerOfRegs and UserOfRegs typeclasses, so if a set of registers defined or used by a node should ever change, `conflicts` function will use the changed definition. This definition also catches more cases than the previous one (namely CmmCall and CmmForeignCall) which is a step towards making it possible to run sinking pass before stack layout (currently this doesn't work). This patch also adds a lot of comments that are result of about two-week long investigation of how sinking pass works and why it does what it does.
-
Jan Stolarek authored
And remove some trailing whitespaces from that file.
-
Austin Seipp authored
This patch implements a warning when definitions conflict with the Applicative-Monad Proposal (AMP), described in #8004. Namely, this will cause a warning iff: * You have an instance of Monad, but not Applicative * You have an instance of MonadPlus, but not Alternative * You locally defined a function named join, <*>, or pure. In GHC 7.10, these warnings will actually be enforced with superclass constraints through changes in base, so programs will fail to compile then. This warning is enabled by default. Unfortunately, not all of our upstream libraries have accepted the appropriate patches. So we temporarily fix ./validate by ignoring the AMP warning. Dan Rosén made an initial implementation of this change, and the remaining work was finished off by David Luposchainsky. I finally made some minor refactorings. Authored-by:
Dan Rosén <danr@chalmers.se> Authored-by:
David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- Sep 11, 2013
-
-
Austin Seipp authored
Authored-by:
David Luposchainsky <dluposchainsky@gmail.com> Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Joachim Breitner authored
-
Herbert Valerio Riedel authored
-
Jan Stolarek authored
On some architectures it might happen that stack layout pass will invalidate the list of calculated procpoints by dropping some of them. We fix this by checking whether a proc-point is in a graph at the beginning of proc-point analysis. This is a speculative fix for #8205.
-
Herbert Valerio Riedel authored
This commit addresses #8051 by fixing - Incorrect column indices reported in error messages for single-line and multi-line input, - incorrect line numbers reported in error messages for expressions entered in multi-line input, and - inhibiting the confusing interaction between `:{` and `:set +m` causing the triggering of implicit multi-line continuation mode right after `:}` terminates the multi-line entry block.
-
Herbert Valerio Riedel authored
This is related to #8121
-
- Sep 10, 2013
-
-
nfrisby authored
'tcRnModuleTcRnM' builds the TcRnM monad computation that is the bulk of 'tcRnModule' This commit makes it simpler for courageous Core plugins to invoke the typechecker. In particular, they no longer need to copy-and-paste what is now the body of 'tcRnModuleTcRnM'. The key change is that the 'tcRnModuleTcRnM' computation can be run with (a hypothetical) 'initTcFromCoreM' instead of 'initTc'.
-
Simon Peyton Jones authored
This patch makes a number of related improvements: * Displays relevant bindings in innermost-first order. The inner ones are closer to the error. * Does not display syntactically top-level bindings, unless you say -fno-max-relevant-bindings. This is what Trac #8233 was mainly about * Makes the TopLevelFlag in a TcIdBinder really mean "syntactically top level". It was a bit vague before. There was some associated simplification, because we no longer need to pas a TopLevelFlag to tcMonoBinds and friends.
-
Simon Peyton Jones authored
See Note [Quantification with errors] Fixes Trac #8262
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
-
Jan Stolarek authored
-
Austin Seipp authored
This is what I get for being so hasty for release notes. Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
Austin Seipp authored
7.6 deprecated the Control.Concurrent.QSem module (to be removed later,) but according to Patrick it was actually un-deprecated. As a result, validate fails if your bootstrap compiler is 7.6, since it throws a DEPRECATED warning. Signed-off-by:
Austin Seipp <austin@well-typed.com>
-
- Sep 09, 2013
-
-
parcs authored
-
Richard Eisenberg authored
-
Richard Eisenberg authored
-
Austin Seipp authored
In 9e133b, the build was modified to pass -fcmm-sink to Parser, but unfortunately Parser specifies -O0 in its OPTIONS_GHC directive, meaning the sinking pass was actually turned off. HC_OPTS is the last thing passed to the compiler for that source file however, so the correct fix is to also move -O0 out into the build system as well. This was uncovered thanks to a build report from Kazu Yamamoto. Thanks to Jan Stolarek for eyeballing this bug and finding it. Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
jpm@cs.ox.ac.uk authored
-
parcs authored
-
- Sep 08, 2013
-
-
Austin Seipp authored
This reverts commit c798a8c6.
-
Austin Seipp authored
This reverts commit d85044f6.
-
Austin Seipp authored
Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
takano-akio authored
This reverts commit 6770663f. If the program enters the garbage collector with the closure lock held, it will confuse the garbage collector and will result in an infinite loop in evacuate(). Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
Austin Seipp authored
When servicing a stack overflows, only throw an exception to the given thread if the user explicitly set a max stack size, using +RTS -K. Otherwise just service it normally and grow the stack. In case we actually run out of *heap* (stack chuncks are allocated on the heap), then we need to bail by calling the stackOverflow() hook and exit immediately. Authored-by:
Ben Gamari <bgamari.foss@gmail.com> Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
nfrisby authored
also added -fdmd-tx-dict-sel, on by default
-
- Sep 07, 2013
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@mit.edu>
-
It was sorted by version number so far. I also added a sort to the normal output (without --simple-output) since the source it comes from does not guarantee sortedness. Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
- Sep 06, 2013
-
-
Austin Seipp authored
This patch encompasses most of the basic infrastructure for GHCJS. It includes: * A new extension, -XJavaScriptFFI * A new architecture, ArchJavaScript * Parser and lexer support for 'foreign import javascript', only available under -XJavaScriptFFI, using ArchJavaScript. * As a knock-on, there is also a new 'WayCustom' constructor in DynFlags, so clients of the GHC API can add custom 'tags' to their built files. This should be useful for other users as well. The remaining changes are really just the resulting fallout, making sure all the cases are handled appropriately for DynFlags and Platform. Authored-by:
Luite Stegeman <stegeman@gmail.com> Signed-off-by:
Austin Seipp <aseipp@pobox.com>
-
parcs authored
-
parcs authored
-
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@mit.edu>
-
Edward Z. Yang authored
Signed-off-by:
Edward Z. Yang <ezyang@mit.edu>
-