- 12 Sep, 2017 1 commit
-
-
Joachim Breitner authored
the worker/wrapper creates an artificial INLINE pragma, which caused CSE to not do its work. We now recognize such artificial pragmas by using `NoUserInline` instead of `Inline` as the `InlineSpec`. Differential Revision: https://phabricator.haskell.org/D3939
-
- 09 Sep, 2017 4 commits
-
-
Herbert Valerio Riedel authored
IOW, code compiles -Wnoncanonical-monoidfail-instances clean now This is easy now since we require GHC 8.0/base-4.9 or later for bootstrapping. Note that we can easily enable `MonadFail` via default-extensions: MonadFailDesugaring in compiler/ghc.cabal.in which currently would point out that NatM doesn't have a proper `fail` method, even though failable patterns are made use of: compiler/nativeGen/SPARC/CodeGen.hs:425:25: error: * No instance for (Control.Monad.Fail.MonadFail NatM) arising from a do statement with the failable pattern ‘(dyn_c, [dyn_r])’
-
Herbert Valerio Riedel authored
IOW, code compiles -Wnoncanonical-monoid-instances clean now
-
Herbert Valerio Riedel authored
In the past we needed the construct below for wired-in packages, but since GHC 8.0 (which we require at least for stage0 now) the CLI has stabilised, so we can unconditionally use `-this-unit-id` since GHC 8.0. if impl( ghc >= 7.11 ) ghc-options: -this-unit-id template-haskell else if impl( ghc >= 7.9 ) ghc-options: -this-package-key template-haskell else ghc-options: -package-name template-haskell
-
Herbert Valerio Riedel authored
Resulting from requiring to boot with GHC 8.0 or later
-
- 08 Sep, 2017 2 commits
-
-
David Feuer authored
The renamer wasn't able to deal with more than a couple strict patterns in a row with `ApplicativeDo` when using the heuristic splitter. Update it to work with them properly. Reviewers: simonmar, austin, bgamari, hvr Reviewed By: simonmar Subscribers: RyanGlScott, lippling, rwbarton, thomie GHC Trac Issues: #14163 Differential Revision: https://phabricator.haskell.org/D3900
-
Moritz Angermann authored
As far as GHC is concerned, iOS **is** Darwin, and Android **is** Linux. Depends on D3352 Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: Ericson2314, ryantrinkle, rwbarton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D3579
-
- 07 Sep, 2017 3 commits
-
-
Herbert Valerio Riedel authored
Unfortunately, this requires introducing a couple of .hs-boot files to break up import cycles (mostly to provide class & typenames in order to be able to write type signatures). This does not yet re-export `(<>)` from Prelude (while the class-name `Semigroup` is reexported); that will happen in a future commit. Test Plan: local ./validate passed Reviewers: ekmett, austin, bgamari, erikd, RyanGlScott Reviewed By: ekmett, RyanGlScott GHC Trac Issues: #14191 Differential Revision: https://phabricator.haskell.org/D3927
-
Gabor Greif authored
-
Gabor Greif authored
-
- 06 Sep, 2017 2 commits
-
-
Gabor Greif authored
and join type signatures
-
Moritz Angermann authored
The LLVM backend shells out to LLVMs `opt` and `llc` tools. This clean up introduces a shared data structure to carry the arguments we pass to each tool so that corresponding flags are next to each other. It drops the hard coded data layouts in favor of using `-mtriple` and have LLVM infer them. Furthermore we add `clang` as a proper tool, so we don't rely on assuming that `clang` is called `clang` on the `PATH` when using `clang` as the assembler. Finally this diff also changes the type of `optLevel` from `Int` to `Word`, as we do not have negative optimization levels. Reviewers: erikd, hvr, austin, rwbarton, bgamari, kavon Reviewed By: kavon Subscribers: michalt, Ericson2314, ryantrinkle, dfeuer, carter, simonpj, kavon, simonmar, thomie, erikd, snowleopard Differential Revision: https://phabricator.haskell.org/D3352
-
- 05 Sep, 2017 5 commits
-
-
Ryan Scott authored
Summary: Before, there was a discrepancy in how GHC renamed type synonyms as opposed to type family instances. That is, GHC would accept definitions like this one: ```lang=haskell type T = (Nothing :: Maybe a) ``` However, it would not accept a very similar type family instance: ```lang=haskell type family T :: Maybe a type instance T = (Nothing :: Maybe a) ``` The primary goal of this patch is to bring the renaming of type family instances up to par with that of type synonyms, causing the latter definition to be accepted, and fixing #14131. In particular, we now allow kind variables on the right-hand sides of type (and data) family instances to be //implicitly// bound by LHS type (or kind) patterns (as opposed to type variables, which must always be explicitly bound by LHS type patterns only). As a consequence, this allows programs reported in #7938 and #9574 to typecheck, whereas before they would have been rejected. Implementation-wise, there isn't much trickery involved in making this happen. We simply need to bind additional kind variables from the RHS of a type family in the right place (in particular, see `RnSource.rnFamInstEqn`, which has undergone a minor facelift). While doing this has the upside of fixing #14131, it also made it easier to trigger #13985, so I decided to fix that while I was in town. This was accomplished by a careful blast of `reportFloatingKvs` in `tcFamTyPats`. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13985, #14131 Differential Revision: https://phabricator.haskell.org/D3872
-
Ben Gamari authored
Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3921
-
Ben Gamari authored
Previously SetLevels.lvlMFE would fail to substitute in ticks, unlike lvlExpr. This lead to #13481. Fix this. Test Plan: `make test TEST=T12622 WAY=ghci` Reviewers: austin, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie GHC Trac Issues: #13481 Differential Revision: https://phabricator.haskell.org/D3920
-
Ryan Scott authored
`RnTypes` contains a fairly intricate algorithm to extract the kind and type variables of an HsType. This algorithm carefully maintains the separation between type variables and kind variables so that the difference between `-XPolyKinds` and `-XTypeInType` can be respected. But after doing all this, `rmDupsInRdrTyVars` stupidly just concatenated the lists of type and kind variables at the end. If a variable were used as both a type and a kind, the algorithm would produce *both*! This led to all kinds of problems, including #13988. This is mostly Richard Eisenberg's patch. The only original contribution I made was adapting call sites of `rnImplicitBndrs` to work with the new definition of `rmDupsInRdrTyVars`. That is, `rnImplicitBndrs` checks for variables that are illegally used in both type and kind positions without using `-XTypeInType`, but in order to check this, one cannot have filtered duplicate variables out before passing them to `rnImplicitBndrs`. To accommodate for this, I needed to concoct variations on the existing `extract-` functions in `RnTypes` which do not remove duplicates, and use those near `rnImplicitBndrs` call sites. test case: ghci/scripts/T13988 Test Plan: make test TEST=T13988 Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: goldfire, simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #13988 Differential Revision: https://phabricator.haskell.org/D3902
-
alexbiehl authored
This is another take on https://phabricator.haskell.org/D3844. This patch removes then need for haddock to reimplement the calculation of exported names from modules. Instead when renaming export lists ghc annotates each IE with its exported names. Haddocks current export logic has caused lots of trouble in the past (on the Github issue tracker): - https://github.com/haskell/haddock/issues/121 - https://github.com/haskell/haddock/issues/174 - https://github.com/haskell/haddock/issues/225 - https://github.com/haskell/haddock/issues/344 - https://github.com/haskell/haddock/issues/584 - https://github.com/haskell/haddock/issues/591 - https://github.com/haskell/haddock/issues/597 Updates haddock submodule. Reviewers: austin, bgamari, ezyang Reviewed By: bgamari, ezyang Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3864
-
- 02 Sep, 2017 2 commits
-
-
Ryan Scott authored
Summary: Two places in GHC effectively attempt to //guess// whether a data type was declared using GADT syntax: 1. When reifying a data type in Template Haskell 2. When pretty-printing a data type (e.g., via `:info` in GHCi) But there's no need for heuristics here, since we have a 100% accurate way to determine whether a data type was declared using GADT syntax: the `isGadtSyntaxTyCon` function! By simply using that as the metric, we obtain far more accurate TH reification and pretty-printing results. This is technically a breaking change, since Template Haskell reification will now reify some data type constructors as `(Rec)GadtC` that it didn't before, and some data type constructors that were previously reified as `(Rec)GadtC` will no longer be reified as such. But it's a very understandable breaking change, since the previous behavior was simply incorrect. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #14167 Differential Revision: https://phabricator.haskell.org/D3901
-
Ryan Scott authored
Summary: GHC was allowing implicitly bidirectional pattern synonyms with bang patterns and irrefutable patterns in the RHS, like so: ```lang=haskell pattern StrictJust a = Just !a ``` This has multiple problems: 1. `Just !a` isn't a valid expression, so it feels strange to allow it in an implicitly bidirectional pattern synonym. 2. `StrictJust` doesn't provide the strictness properties one would expect from a strict constructor. (One could imagine a design where the `StrictJust` builder infers a bang pattern for its pattern variable, but accomplishing this inference in a way that accounts for all possible patterns on the RHS, including other pattern synonyms, is somewhat awkward, so we do not pursue this design.) We nip these issues in the bud by simply disallowing bang/irrefutable patterns on the RHS. Test Plan: make test TEST="T14112 unidir" Reviewers: simonpj, austin, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie GHC Trac Issues: #14112 Differential Revision: https://phabricator.haskell.org/D3896
-
- 01 Sep, 2017 1 commit
-
-
Ben Gamari authored
Test Plan: Added testcase in D3905. Reviewers: austin Subscribers: angerman, rwbarton, thomie GHC Trac Issues: #14178 Differential Revision: https://phabricator.haskell.org/D3904
-
- 31 Aug, 2017 4 commits
-
-
Herbert Valerio Riedel authored
This is a pre-requisite for implementing the Semigroup/Monoid proposal. The instances have been introduced in a way to minimise warnings.
-
Simon Peyton Jones authored
I dug more into how #14158 started working. I temporarily reverted the patch that "fixed" it, namely commit a6c448b4 Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Mon Aug 28 17:33:59 2017 +0100 Small refactor of getRuntimeRep Sure enough, there was a real bug, described in the new TcExpr Note [Visible type application zonk] In general, syntactic substituion should be kind-preserving! Maybe we should check that invariant...
-
Simon Peyton Jones authored
-
Simon Peyton Jones authored
We pretty-print a type by converting it to an IfaceType and pretty-printing that. But (a) that's a bit indirect, and (b) delibrately loses information about (e.g.) the kind on the /occurrences/ of a type variable So this patch implements debugPprType, which pretty prints the type directly, with no fancy formatting. It's just used for debugging. I took the opportunity to refactor the debug-pretty-printing machinery a little. In particular, define these functions and use them: ifPprDeubug :: SDoc -> SDOc -> SDoc -- Says what to do with and without -dppr-debug whenPprDebug :: SDoc -> SDoc -- Says what to do with -dppr-debug; without is empty getPprDebug :: (Bool -> SDoc) -> SDoc getPprDebug used to be called sdocPprDebugWith whenPprDebug used to be called ifPprDebug So a lot of files get touched in a very mechanical way
-
- 30 Aug, 2017 3 commits
-
-
Simon Peyton Jones authored
All this Left/Right business was making my head spin, so I defined data HsArg tm ty = HsValArg tm -- Argument is an ordinary expression (f arg) | HsTypeArg ty -- Argument is a visible type application (f @ty) and used it. This is just simple refactor; no change in behaviour.
-
Simon Peyton Jones authored
These comments clarify the details of: commit 0257dacf Author: Simon Peyton Jones <simonpj@microsoft.com> Date: Mon Aug 28 14:20:02 2017 +0100 Refactor bindHsQTyVars and friends
-
Simon Peyton Jones authored
I added these when investigating Trac #14163, but they'll be useful anyway.
-
- 29 Aug, 2017 13 commits
-
-
Ben Gamari authored
I prematurely committed the D3892 before adding a Note. Fix this.
-
James Michael DuPont authored
-
Ben Gamari authored
We used to try a crude comparison of the type themselves, but this is essentially impossible in STG as we have discarded. both casts and type applications, so types might look different but be the same. Now we simply compare their runtime representations. See #14120. Reviewers: austin Subscribers: rwbarton, thomie GHC Trac Issues: #14120 Differential Revision: https://phabricator.haskell.org/D3879
-
Ben Gamari authored
The unariser ensures that we never use case binders that are void, unboxed sums, or unboxed tuples. However, previously StgLint was enforcing this invariant even before the unariser was running, giving rise to spurious lint failures. Fix this. Following CoreLint, we introduce a LintFlags environment to the linter monad, allowing for additional flags to be easily accomodated in the future. See #14118. Test Plan: Build GHC with -dstg-lint Reviewers: simonpj, austin Subscribers: rwbarton, thomie GHC Trac Issues: #14118 Differential Revision: https://phabricator.haskell.org/D3889
-
Ben Gamari authored
Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3887
-
Ben Gamari authored
There were a couple places where we indexed into linked lists of register names. Replace these with arrays. Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3893
-
Tamar Christina authored
Summary: Fix the path decomposition error that occurs when the Symlink resolver fails. `Win32.try` throws an exception, so catch it and assume the path isn't a symlink to use the old behavior. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie GHC Trac Issues: #14159 Differential Revision: https://phabricator.haskell.org/D3891
-
Ryan Scott authored
This implements @simonpj's suggested refactoring of the abstract syntax for type/data family instances (from https://ghc.haskell.org/trac/ghc/ticket/14131#comment:9). This combines the previously separate `TyFamEqn` and `DataFamInstDecl` types into a single `FamEqn` datatype. This also factors the `HsImplicitBndrs` out of `HsTyPats` in favor of putting them just outside of `FamEqn` (as opposed to before, where all of the implicit binders were embedded inside of `TyFamEqn`/`DataFamInstDecl`). Finally, along the way I noticed that `dfid_fvs` and `tfid_fvs` were completely unused, so I removed them. Aside from some changes in parser test output, there is no change in behavior. Requires a Haddock submodule commit from my fork (at https://github.com/RyanGlScott/haddock/commit/815d2deb9c0222c916becccf84 64b740c26255fd) Test Plan: ./validate Reviewers: simonpj, austin, goldfire, bgamari, alanz Reviewed By: bgamari Subscribers: mpickering, goldfire, rwbarton, thomie, simonpj GHC Trac Issues: #14131 Differential Revision: https://phabricator.haskell.org/D3881
-
Tamar Christina authored
This patch removes dll-split from the code base, the reason is dll-split no longer makes any sense. It was designed to split a dll in two, but we now already have many more symbols than would fit inside two dlls. So we need a third one. This means there's no point in having to maintain this list as it'll never work anyway and the solution isn't scalable. Test Plan: ./validate Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, #ghc_windows_task_force GHC Trac Issues: #5987 Differential Revision: https://phabricator.haskell.org/D3882
-
Ben Gamari authored
Consider that we have two modules, A and B, both with hs-boot files, * A.hs contains a SOURCE import of B * B.hs-boot contains a SOURCE import of A * A.hs-boot declares an orphan instance * A.hs defines the orphan instance In this case, B's dep_orphs will contain A due to its SOURCE import of A. Consequently, A will contain itself in its imp_orphs due to its import of B. This fact would end up being recorded in A's interface file. This would then break the invariant asserted by calculateAvails that a module does not itself in its dep_orphs. This was the cause of #14128. The solution is to remove self-references from imp_orphs when constructing dep_orphs; we already did a similar thing for dep_mods. I believe we should do the same for dep_finsts, although I'm treating this as a separate bug. Reviewers: austin Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D3892
-
Simon Peyton Jones authored
typeKind can fail, and it's called all over the place, so it's helpful to know where
-
Simon Peyton Jones authored
Instead of using a string argument, use HasDebugCallStack. (Oddly, some functions were using both!) Plus, use getRuntimeRep rather than getRuntimeRep_maybe when if the caller panics on Nothing. Less code, and a better debug stack.
-
Simon Peyton Jones authored
-