summaryrefslogtreecommitdiff
path: root/compiler
Commit message (Collapse)AuthorAgeFilesLines
...
* Only skip decls with CUSKs with PolyKinds on (fix #16609)Ningning Xie2019-05-031-7/+26
|
* Pattern/expression ambiguity resolutionVladislav Zavialov2019-05-039-598/+866
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This patch removes 'EWildPat', 'EAsPat', 'EViewPat', and 'ELazyPat' from 'HsExpr' by using the ambiguity resolution system introduced earlier for the command/expression ambiguity. Problem: there are places in the grammar where we do not know whether we are parsing an expression or a pattern, for example: do { Con a b <- x } -- 'Con a b' is a pattern do { Con a b } -- 'Con a b' is an expression Until we encounter binding syntax (<-) we don't know whether to parse 'Con a b' as an expression or a pattern. The old solution was to parse as HsExpr always, and rejig later: checkPattern :: LHsExpr GhcPs -> P (LPat GhcPs) This meant polluting 'HsExpr' with pattern-related constructors. In other words, limitations of the parser were affecting the AST, and all other code (the renamer, the typechecker) had to deal with these extra constructors. We fix this abstraction leak by parsing into an overloaded representation: class DisambECP b where ... newtype ECP = ECP { runECP_PV :: forall b. DisambECP b => PV (Located b) } See Note [Ambiguous syntactic categories] for details. Now the intricacies of parsing have no effect on the hsSyn AST when it comes to the expression/pattern ambiguity.
* Emit GHC timing events to eventlogBen Gamari2019-04-301-0/+2
|
* ErrUtils: Emit progress messages to eventlogBen Gamari2019-04-301-3/+5
|
* Move cGHC_UNLIT_PGM to be "unlit command" in settingsJohn Ericson2019-04-302-5/+3
| | | | | | | | | | | | The bulk of the work was done in #712, making settings be make/Hadrian controlled. This commit then just moves the unlit command rules in make/Hadrian from the `Config.hs` generator to the `settings` generator in each build system. I think this is a good change because the crucial benefit is *settings* don't affect the build: ghc gets one baby step closer to being a regular cabal executable, and make/Hadrian just maintains settings as part of bootstrapping.
* Compute demand signatures assuming idAritySebastian Graf2019-04-3012-174/+396
| | | | | | | | | | | | | | | | | | | | | | | | | | | | This does four things: 1. Look at `idArity` instead of manifest lambdas to decide whether to use LetUp 2. Compute the strictness signature in LetDown assuming at least `idArity` incoming arguments 3. Remove the special case for trivial RHSs, which is subsumed by 2 4. Don't perform the W/W split when doing so would eta expand a binding. Otherwise we would eta expand PAPs, causing unnecessary churn in the Simplifier. NoFib Results -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- fannkuch-redux +0.3% 0.0% gg -0.0% -0.1% maillist +0.2% +0.2% minimax 0.0% +0.8% pretty 0.0% -0.1% reptile -0.0% -1.2% -------------------------------------------------------------------------------- Min -0.0% -1.2% Max +0.3% +0.8% Geometric Mean +0.0% -0.0%
* Use pp_itemWojciech Baranowski2019-04-291-3/+1
|
* Suggest only local candidates from global envWojciech Baranowski2019-04-291-2/+4
|
* Comment on 'candidates' functionWojciech Baranowski2019-04-291-0/+2
|
* osa1's patch: consistent suggestion messageWojciech Baranowski2019-04-291-3/+4
|
* Print suggestions in a single messageWojciech Baranowski2019-04-291-5/+7
|
* rename: hadle type signatures with typosWojciech Baranowski2019-04-291-2/+18
| | | | | | | When encountering type signatures for unknown names, suggest similar alternatives. This fixes issue #16504
* checkPattern error hint is PV contextVladislav Zavialov2019-04-253-90/+136
| | | | | There is a hint added to error messages reported in checkPattern. Instead of passing it manually, we put it in a ReaderT environment inside PV.
* Introduce MonadP, make PV a newtypeVladislav Zavialov2019-04-253-73/+104
| | | | | | | | | | | Previously we defined type PV = P, this had the downside that if we wanted to change PV, we would have to modify P as well. Now PV is free to evolve independently from P. The common operations addError, addFatalError, getBit, addAnnsAt, were abstracted into a class called MonadP.
* Stop misusing EWildPat in pattern match coverage checkingVladislav Zavialov2019-04-221-27/+22
| | | | | | | | | | | | | | | | EWildPat is a constructor of HsExpr used in the parser to represent wildcards in ambiguous positions: * in expression context, EWildPat is turned into hsHoleExpr (see rnExpr) * in pattern context, EWildPat is turned into WildPat (see checkPattern) Since EWildPat exists solely for the needs of the parser, we could remove it by improving the parser. However, EWildPat has also been used for a different purpose since 8a50610: to represent patterns that the coverage checker cannot handle. Not only this is a misuse of EWildPat, it also stymies the removal of EWildPat.
* [skip ci] correct the docs for casArray a little more. clarify that the ↵Andrew Martin2019-04-211-3/+5
| | | | returned element may be two different things
* [skip ci] correct formatting of casArray# in docs for casSmallArray#Andrew Martin2019-04-211-1/+1
|
* [skip ci] say "machine words" instead of "Int units" in the primops docsAndrew Martin2019-04-211-16/+19
|
* improve docs for casArray and casSmallArrayAndrew Martin2019-04-211-1/+8
|
* Haddock: support strict GADT args with docsAlec Theriault2019-04-192-29/+13
| | | | | | | | | Rather than massaging the output of the parser to re-arrange docs and bangs, it is simpler to patch the two places in which the strictness info is needed (to accept that the `HsBangTy` may be inside an `HsDocTy`). Fixes #16585.
* Tagless final encoding of ExpCmdI in the parserVladislav Zavialov2019-04-191-122/+131
| | | | | | | | | | | Before this change, we used a roundabout encoding: 1. a GADT (ExpCmdG) 2. a class to pass it around (ExpCmdI) 3. helpers to match on it (ecHsApp, ecHsIf, ecHsCase, ...) It is more straightforward to turn these helpers into class methods, removing the need for a GADT.
* Don't indent single alternative case expressions for STG.klebinger.andreas@gmx.at2019-04-191-5/+18
| | | | | | | Makes the width of STG dumps slightly saner. Especially for things like unboxing. Fixes #16580
* StgCmmPrim: remove an unnecessary instruction in doNewArrayOpMichal Terepeta2019-04-191-5/+2
| | | | | | | | | | | Previously we would generate a local variable pointing after the array header and use it to initialize the array elements. But we already use stores with offset, so it's easy to just add the header to those offsets during compilation and avoid generating the local variable (which would become a LEA instruction when using native codegen; LLVM already optimizes it away). Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com>
* TH: make `Lift` and `TExp` levity-polymorphicAlec Theriault2019-04-187-88/+61
| | | | | | | | | | | | | | | | | | | | | | | | | | | | Besides the obvious benefits of being able to manipulate `TExp`'s of unboxed types, this also simplified `-XDeriveLift` all while making it more capable. * `ghc-prim` is explicitly depended upon by `template-haskell` * The following TH things are parametrized over `RuntimeRep`: - `TExp(..)` - `unTypeQ` - `unsafeTExpCoerce` - `Lift(..)` * The following instances have been added to `Lift`: - `Int#`, `Word#`, `Float#`, `Double#`, `Char#`, `Addr#` - unboxed tuples of lifted types up to arity 7 - unboxed sums of lifted types up to arity 7 Ideally we would have levity-polymorphic _instances_ of unboxed tuples and sums. * The code generated by `-XDeriveLift` uses expression quotes instead of generating large amounts of TH code and having special hard-coded cases for some unboxed types.
* Add an Outputable instance for SDoc with ppr = id.klebinger.andreas@gmx.at2019-04-171-0/+4
| | | | When printf debugging this can be helpful.
* Show dynamic object files (#16062)erthalion2019-04-162-12/+28
| | | | | | | | | | | | | Closes #16062. When -dynamic-too is specified, reflect that in the progress message, like: $ ghc Main.hs -dynamic-too [1 of 1] Compiling Lib ( Main.hs, Main.o, Main.dyn_o ) instead of: $ ghc Main.hs -dynamic-too [1 of 1] Compiling Lib ( Main.hs, Main.o )
* asm-emit-time IND_STATIC eliminationGabor Greif2019-04-159-11/+234
| | | | | | | | | | | | When a new closure identifier is being established to a local or exported closure already emitted into the same module, refrain from adding an IND_STATIC closure, and instead emit an assembly-language alias. Inter-module IND_STATIC objects still remain, and need to be addressed by other measures. Binary-size savings on nofib are around 0.1%.
* Add a safeguard to Core LintKrzysztof Gogolewski2019-04-141-3/+6
| | | | | | | | | Lint returns a pair (Maybe a, WarnsAndErrs). The Maybe monad allows to handle an unrecoverable failure. In case of such a failure, the error should be added to the second component of the pair. If this is not done, Lint will silently accept bad programs. This situation actually happened during development of linear types. This adds a safeguard.
* codegen: unroll memcpy calls for small bytearraysArtem Pyanykh2019-04-143-30/+42
|
* Fix assertion failures reported in #16533Krzysztof Gogolewski2019-04-144-5/+5
|
* Add -ddump-stg-final to dump stg as it is used for codegen.klebinger.andreas@gmx.at2019-04-122-0/+5
| | | | | Intermediate STG does not contain free variables which can be useful sometimes. So adding a flag to dump that info.
* Update a panic messageÖmer Sinan Ağacan2019-04-111-2/+2
| | | | Point users to the right URL
* removing x87 register support from native code genCarter Schonwald2019-04-1024-914/+291
| | | | | | | | | | | | | | | | * simplifies registers to have GPR, Float and Double, by removing the SSE2 and X87 Constructors * makes -msse2 assumed/default for x86 platforms, fixing a long standing nondeterminism in rounding behavior in 32bit haskell code * removes the 80bit floating point representation from the supported float sizes * theres still 1 tiny bit of x87 support needed, for handling float and double return values in FFI calls wrt the C ABI on x86_32, but this one piece does not leak into the rest of NCG. * Lots of code thats not been touched in a long time got deleted as a consequence of all of this all in all, this change paves the way towards a lot of future further improvements in how GHC handles floating point computations, along with making the native code gen more accessible to a larger pool of contributors.
* GHC no longer ever defines TABLES_NEXT_TO_CODE on its ownJoachim Breitner2019-04-092-8/+2
| | | | | | | | | | | | | | | It should be entirely the responsibility of make/Hadrian to ensure that everything that needs this flag gets it. GHC shouldn't be hardcoded to assist with bootstrapping since it builds other things besides itself. Reviewers: Subscribers: TerrorJack, rwbarton, carter GHC Trac Issues: #15548 -- progress towards but not fix Differential Revision: https://phabricator.haskell.org/D5082 -- extract from that
* codegen: use newtype for Alignment in BasicTypesArtem Pyanykh2019-04-096-48/+71
|
* codegen: fix memset unroll for small bytearrays, add 64-bit setsArtem Pyanykh2019-04-093-29/+77
| | | | | | | | | | | | | | | | | | | | | | Fixes #16052 When the offset in `setByteArray#` is statically known, we can provide better alignment guarantees then just 1 byte. Also, memset can now do 64-bit wide sets. The current memset intrinsic is not optimal however and can be improved for the case when we know that we deal with (baseAddress at known alignment) + offset For instance, on 64-bit `setByteArray# s 1# 23# 0#` given that bytearray is 8 bytes aligned could be unrolled into `movb, movw, movl, movq, movq`; but currently it is `movb x23` since alignment of 1 is all we can embed into MO_Memset op.
* Make `singleConstructor` cope with pattern synonymsSebastian Graf2019-04-081-53/+92
| | | | | | | | | | | | | | | Previously, `singleConstructor` didn't handle singleton `COMPLETE` sets of a single pattern synonym, resulting in incomplete pattern warnings in #15753. This is fixed by making `singleConstructor` (now named `singleMatchConstructor`) query `allCompleteMatches`, necessarily making it effectful. As a result, most of this patch is concerned with threading the side-effect through to `singleMatchConstructor`. Unfortunately, this is not enough to completely fix the original reproduction from #15753 and #15884, which are related to function applications in pattern guards being translated too conservatively.
* Add `-optcxx` option (#16477)Yuriy Syrovetskiy2019-04-087-20/+49
|
* Fix #16500: look for interface files in -hidir flag in OneShot modePhuong Trinh2019-04-081-2/+13
| | | | | | | | | | | We are currently ignoring options set in the hiDir field of hsc_dflags when looking for interface files while compiling in OneShot mode. This is inconsistent with the behaviour of other directory redirecting fields (such as objectDir or hieDir). It is also inconsistent with the behaviour of compilation in CompManager mode (a.k.a `ghc --make`) which looks for interface files in the directory set in hidir flag. This changes Finder.hs so that we use the value of hiDir while looking for interface in OneShot mode.
* Generate straightline code for inline array allocationMichal Terepeta2019-04-081-11/+5
| | | | | | | | | | | | | | | GHC has an optimization for allocating arrays when the size is statically known -- it'll generate the code allocating and initializing the array inline (instead of a call to a procedure from `rts/PrimOps.cmm`). However, the generated code uses a loop to do the initialization. Since we already check that the requested size is small (we check against `maxInlineAllocSize`), we can generate faster straightline code instead. This brings about 15% improvement for `newSmallArray#` in my testing and slightly simplifies the code in GHC. Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com>
* Fix #16282.Eric Crockett2019-04-072-24/+31
| | | | | | | Previously, -W(all-)missed-specs was created with 'NoReason', so no information about the flag was printed along with the warning. Now, -Wall-missed-specs is listed as the Reason if it was set, otherwise -Wmissed-specs is listed as the reason.
* Tweak error messages for narrowly-kinded assoc default declsRyan Scott2019-04-041-24/+60
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | This program, from #13971, currently has a rather confusing error message: ```hs class C a where type T a :: k type T a = Int ``` ``` • Kind mis-match on LHS of default declaration for ‘T’ • In the default type instance declaration for ‘T’ In the class declaration for ‘C’ ``` It's not at all obvious why GHC is complaining about the LHS until you realize that the default, when printed with `-fprint-explicit-kinds`, is actually `type T @{k} @* a = Int`. That is to say, the kind of `a` is being instantiated to `Type`, whereas it ought to be a kind variable. The primary thrust of this patch is to weak the error message to make this connection more obvious: ``` • Illegal argument ‘*’ in: ‘type T @{k} @* a = Int’ The arguments to ‘T’ must all be type variables • In the default type instance declaration for ‘T’ In the class declaration for ‘C’ ``` Along the way, I performed some code cleanup suggested by @rae in https://gitlab.haskell.org/ghc/ghc/issues/13971#note_191287. Before, we were creating a substitution from the default declaration's type variables to the type family tycon's type variables by way of `tcMatchTys`. But this is overkill, since we already know (from the aforementioned validity checking) that all the arguments in a default declaration must be type variables anyway. Therefore, creating the substitution is as simple as using `zipTvSubst`. I took the opportunity to perform this refactoring while I was in town. Fixes #13971.
* Use funPrec, not topPrec, to parenthesize GADT argument typesRyan Scott2019-04-041-8/+13
| | | | A simple oversight. Fixes #16527.
* Fix #16518 with some more kind-splitting smartsRyan Scott2019-04-042-16/+38
| | | | | | | | | | | | | | | | This patch corrects two simple oversights that led to #16518: 1. `HsUtils.typeToLHsType` was taking visibility into account in the `TyConApp` case, but not the `AppTy` case. I've factored out the visibility-related logic into its own `go_app` function and now invoke `go_app` from both the `TyConApp` and `AppTy` cases. 2. `Type.fun_kind_arg_flags` did not properly split kinds with nested `forall`s, such as `(forall k. k -> Type) -> (forall k. k -> Type)`. This was simply because `fun_kind_arg_flags`'s `FunTy` case always bailed out and assumed all subsequent arguments were `Required`, which clearly isn't the case for nested `forall`s. I tweaked the `FunTy` case to recur on the result kind.
* Fix Uncovered set of literal patternsSebastian Graf2019-04-032-5/+14
| | | | | | | | | | | | | | | | Issues #16289 and #15713 are proof that the pattern match checker did an unsound job of estimating the value set abstraction corresponding to the uncovered set. The reason is that the fix from #11303 introducing `NLit` was incomplete: The `LitCon` case desugared to `Var` rather than `LitVar`, which would have done the necessary case splitting analogous to the `ConVar` case. This patch rectifies that by introducing the fresh unification variable in `LitCon` in value abstraction position rather than pattern postition, recording a constraint equating it to the constructor expression rather than the literal. Fixes #16289 and #15713.
* Correct two misspellings of "separately"Chris Martin2019-04-031-1/+1
|
* Fix faulty substitutions in StgCse (#11532).klebinger.andreas@gmx.at2019-04-031-2/+2
| | | | | | | | | | | | `substBndr` should rename bindings which shadow existing ids. However while it was renaming the bindings it was not adding proper substitutions for renamed bindings. Instead of adding a substitution of the form `old -> new` for renamed bindings it mistakenly added `old -> old` if no replacement had taken place while adding none if `old` had been renamed. As a byproduct this should improve performance, as we no longer add useless substitutions for unshadowed bindings.
* Remove unnecessary uses of UnboxedTuples pragma (see #13101 / #15454)Michael Sloan2019-04-015-5/+4
| | | | Also removes a couple unnecessary MagicHash pragmas
* Add support for bitreverse primopAlexandre2019-04-019-5/+50
| | | | | | This commit includes the necessary changes in code and documentation to support a primop that reverses a word's bits. It also includes a test.
* Visibility: handle multiple units with the same nameMichael Peyton Jones2019-03-291-13/+32
| | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | | Fixes #16228. The included test case is adapted from the reproduction in the issue, and fails without this patch. ------ We compute an initial visilibity mapping for units based on what is present in the package databases. To seed this, we compute a set of all the package configs to add visibilities for. However, this set was keyed off the unit's *package name*. This is correct, since we compare packages across databases by version. However, we would only ever consider a single, most-preferable unit from the database in which it was found. The effect of this was that only one of the libraries in a Cabal package would be added to this initial set. This would cause attempts to use modules from the omitted libraries to fail, claiming that the package was hidden (even though `ghc-pkg` would correctly show it as visible). A solution is to do the selection of the most preferable packages separately, and then be sure to consider exposing all units in the same package in the same package db. We can do this by picking a most-preferable unit for each package name, and then considering exposing all units that are equi-preferable with that unit. ------ Why wasn't this bug apparent to all people trying to use sub-libraries in Cabal? The answer is that Cabal explicitly passes `-package` and `-package-id` flags for all the packages it wants to use, rather than relying on the state of the package database. So this bug only really affects people who are trying to use package databases produced by Cabal outside of Cabal itself. One particular example of this is the way that the Nixpkgs Haskell infrastructure provides wrapped GHCs: typically these are equipped with a package database containing all the needed package dependencies, and the user is not expected to pass `-package` flags explicitly.