| Commit message (Collapse) | Author | Age | Files | Lines |
... | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
For some time now, type-level operators such as '+' have been treated as
type constructors, rahter than type variables. This pathc fixes TH's
`lookupName` function to account for this behavior.
Reviewers: bgamari, austin, goldfire, RyanGlScott
Reviewed By: RyanGlScott
Subscribers: Phyx, thomie
Differential Revision: https://phabricator.haskell.org/D3025
GHC Trac Issues: #11046
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds the flag `-ddump-json` which dumps all the compiler
output as a JSON array. This allows tooling to more easily parse GHC's
output to display to users.
The flag is currently experimental and will hopefully be refined for the
next release. In particular I have avoided any changes which involve
significant refactoring and provided what is easy given the current
infrastructure.
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: DanielG, gracjan, thomie
Differential Revision: https://phabricator.haskell.org/D3010
GHC Trac Issues: #13190
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Before, GHC was extremely permissive about the form a default type
signature could take on in a class declaration. Notably, it would accept
garbage like this:
class Monad m => MonadSupply m where
fresh :: m Integer
default fresh :: MonadTrans t => t m Integer
fresh = lift fresh
And then give an extremely confusing error message when you actually
tried to declare an empty instance of MonadSupply. We now do extra
validity checking of default type signatures to ensure that they align
with their non-default type signature counterparts. That is, a default
type signature is allowed to differ from the non-default one only in its
context - they must otherwise be alpha-equivalent.
Fixes #12918.
Test Plan: ./validate
Reviewers: goldfire, simonpj, austin, bgamari
Reviewed By: bgamari
Subscribers: mpickering, dfeuer, thomie
Differential Revision: https://phabricator.haskell.org/D2983
GHC Trac Issues: #12918
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
1. DoParamM requires the FlexibleContexts pragma now.
2. topHandler02 and topHandler03 were broken as timeout.py failed to
translate signals to exit codes.
3. topHandler03 does not produce a consistent stderr, as it depends on
what the user has /bin/sh set to. dash writes "Terminated" whereas
bash and zsh produce nothing in non-interactive mode.
4. The remaining tests are broken due to changes in the error message
formatting.
Test Plan: validate
Reviewers: thomie, dfeuer, austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: Phyx, dfeuer
Differential Revision: https://phabricator.haskell.org/D2807
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
The functions that were causing warnings were deprecated in containers
0.5 and GHC is already using containers 0.5.9.1.
Test Plan: validate
Reviewers: rwbarton, bgamari, hsyl20, austin, dfeuer
Reviewed By: dfeuer
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3036
|
|
|
|
|
|
|
|
|
| |
[ci skip]
A Generic derivation example in the documentation of GHC.Generics put a tick
(used for datatype promotion) in the wrong place.
Fixes #13206.
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
When toplevel literals don't have a way to be exported
from module GHC infers their labels as static.
Example from GHC.Arr:
static char rdVA_bytes[] = " out of range ";
When this label is used in module internally
we also need to provide it's forward declaration.
Signed-off-by: Sergei Trofimovich <siarheit@google.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Typical UNREG build failure looks like that:
ghc-unreg/includes/Stg.h:226:46: error:
note: in definition of macro 'EI_'
#define EI_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
^
|
226 | #define EI_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
| ^
/tmp/ghc10489_0/ghc_3.hc:1754:6: error:
note: previous definition of 'ghczmprim_GHCziTypes_zdtcTyCon2_bytes' was here
char ghczmprim_GHCziTypes_zdtcTyCon2_bytes[] = "TyCon";
^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
1754 | char ghczmprim_GHCziTypes_zdtcTyCon2_bytes[] = "TyCon";
| ^
As we see here "_bytes" string literals are defined as 'char []'
array, not 'StgWord []'.
The change special-cases "_bytes" string literals to have
correct declaration type.
Signed-off-by: Sergei Trofimovich <siarheit@google.com>
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
There was a `pprTrace` in `isPredTy` that could fire under certain
scenarios, causing normal GHC users to see debugging output. This turns it into
a less chatty `WARN`, and expounds on the comment below it to add the scenario
in #13187 which triggered the `pprTrace`.
Reviewers: goldfire, austin, bgamari
Reviewed By: goldfire, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3033
GHC Trac Issues: #13187
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
On Windows we have to retry the delete a couple of times.
The reason for this is that a `FileDelete` command just marks a
file for deletion. The file is really only removed when the last
handle to the file is closed. Unfortunately there are a lot of
system services that can have a file temporarily opened using a shared
readonly lock, such as the built in AV and search indexer.
We can't really guarantee that these are all off, so what we can do is
whenever after a `rmtree` the folder still exists to try again and wait a bit.
Based on what I've seen from the tests on CI server, is that this is relatively rare.
So overall we won't be retrying a lot. If after a reasonable amount of time the folder is
still locked then abort the current test by throwing an exception, this so it won't fail
with an even more cryptic error.
The issue is that these services often open a file using `FILE_SHARE_DELETE` permissions.
So they can seemingly be removed, and for most intended purposes they are, but recreating
the file with the same name will fail as the FS will prevent data loss.
The MSDN docs for `DeleteFile` says:
```
The DeleteFile function marks a file for deletion on close.
Therefore, the file deletion does not occur until the last handle
to the file is closed. Subsequent calls to CreateFile to open the
file fail with ERROR_ACCESS_DENIED.
```
Retrying seems to be a common pattern, SQLite has it in their driver
http://www.sqlite.org/src/info/89f1848d7f
The only way to avoid this is to run each way of a test in it's own folder.
This would also have the added bonus of increased parallelism.
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: thomie, #ghc_windows_task_force
Differential Revision: https://phabricator.haskell.org/D2936
GHC Trac Issues: #12661, #13162
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
"The tuple data types" seems like an inaccurate way to lead off the
description of this module, which doesn't actually export the tuple data
types. The latter part of the sentence, "associated functions",
accurately describes the entire module.
Reviewers: austin, hvr, bgamari
Reviewed By: bgamari
Subscribers: dfeuer, thomie
Differential Revision: https://phabricator.haskell.org/D2924
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In `x shiftR y`, any of the following conditions cause an abort:
- `x` is a negative big integer
- The size of `x` and `y` is a multiple of `GMP_NUMB_BITS`
- The bit of the absolute value of `x` is filled with `1`
For example:
Assuming `GMP_NUMB_BITS = 2`, the processing of `-15 shiftR 2` is as
follows:
1. -15 = -1111 (twos complement: 10001)
2. right shift 2 (as a positive number) -> 0011
3. Due to the shift larger than GMP_NUMB_BITS, the size of the
destination is decreasing (2bit) -> 11
4. Add 1, and get carry: (1) 00
5. abort
I fixed it that the destination size does not decrease in such a case.
Test Plan: I tested the specific case being reported.
Reviewers: goldfire, austin, hvr, bgamari, rwbarton
Reviewed By: bgamari, rwbarton
Subscribers: mpickering, rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D2998
GHC Trac Issues: #12136
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This isn't supported, and fatalling with an error is better than
segfaulting later.
Test Plan: validate
Reviewers: JonCoens, austin, erikd, niteria, bgamari
Reviewed By: niteria, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3020
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: validate
Reviewers: austin, hvr, bgamari, RyanGlScott, simonpj
Reviewed By: RyanGlScott, simonpj
Subscribers: simonpj, RyanGlScott, thomie
Differential Revision: https://phabricator.haskell.org/D3017
GHC Trac Issues: #12805
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
The addition of rigorous pretty-printer tests
(499e43824bda967546ebf95ee33ec1f84a114a7c) had the unfortunate
side-effect of revealing a bug in `hsSyn/Convert.hs` wherein instances are
_always_ qualified with an instance context, even if the context is empty. This
led to instances like this:
```
instance Foo Int
```
being pretty-printed like this!
```
instance () => Foo Int
```
We can prevent this by checking if the context is empty before adding an
HsQualTy to the type.
Also does some refactoring around HsForAllTys in `Convert` while I was in town.
Fixes #13183.
Test Plan: ./validate
Reviewers: goldfire, bgamari, austin, alanz
Reviewed By: alanz
Subscribers: mpickering, thomie
Differential Revision: https://phabricator.haskell.org/D3018
GHC Trac Issues: #13183
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
At the moment an export of the form
type C(..)
is parsed by the rule
```
| 'type' oqtycon {% amms (mkTypeImpExp (sLL $1 $> (unLoc $2)))
[mj AnnType $1,mj AnnVal $2] }
```
This means that the origiinal oqtycon loses its location which is then retained
in the AnnVal annotation.
The problem is if the oqtycon has its own annotations, these get lost.
e.g. in
type (?)(..)
the parens annotations for (?) get lost.
This patch adds a wrapper around the name in the IE type to
(a) provide a distinct location for the adornment annotation and
(b) identify the specific adornment, for use in the pretty printer rather than
occName magic.
Updates haddock submodule
Test Plan: ./validate
Reviewers: mpickering, dfeuer, bgamari, austin
Reviewed By: dfeuer
Subscribers: dfeuer, thomie, mpickering
Differential Revision: https://phabricator.haskell.org/D3016
GHC Trac Issues: #13163
|
| |
|
| |
|
|
|
|
|
|
|
| |
95dc6dc070deac733d4a4a63a93e606a2e772a67 forgot to add `pragCompleteDName`
to the list of `templateHaskellNames`, which caused a panic if you actually
tried to splice a `COMPLETE` pragma using Template Haskell. This applies the
easy fix and augments the regression test to check for this in the future.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
* Generalize the type of `runRW#` to allow arbitrary return types.
* Use `runRW#` to implement `Control.Monad.ST.Lazy.runST` (this
provides evidence that it actually works properly with the generalized
type).
* Adjust the type signature in the definition of `oneShot` to match
the one it is given in `MkId`.
Reviewers: simonmar, austin, bgamari, hvr
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3012
GHC Trac Issues: #13178
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: RyanGlScott, austin, goldfire, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2997
GHC Trac Issues: #13098
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This patch adds a new pragma so that users can specify `COMPLETE` sets of
`ConLike`s in order to sate the pattern match checker.
A function which matches on all the patterns in a complete grouping
will not cause the exhaustiveness checker to emit warnings.
```
pattern P :: ()
pattern P = ()
{-# COMPLETE P #-}
foo P = ()
```
This example would previously have caused the checker to warn that
all cases were not matched even though matching on `P` is sufficient to
make `foo` covering. With the addition of the pragma, the compiler
will recognise that matching on `P` alone is enough and not emit
any warnings.
Reviewers: goldfire, gkaracha, alanz, austin, bgamari
Reviewed By: alanz
Subscribers: lelf, nomeata, gkaracha, thomie
Differential Revision: https://phabricator.haskell.org/D2669
GHC Trac Issues: #8779
|
|
|
|
|
|
|
|
| |
Reviewers: RyanGlScott, austin, Phyx, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3021
|
| |
|
| |
|
| |
|
|
|
|
|
| |
Gipeda suggests that this is due to the recent top-level string literals in Core
patch.
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Bump the version of `Win32` to `2.5.0.0` which is a major update and includes
fixes for wrong alignments and wrong 64-bit types. Strangely enough this also
seems to resolve #12713, where `T10858` was failing due to too-low allocations.
The underlying type aliases have changed, so there is a potential
for user programs not to compile anymore, but the types were incorrect.
This also requires a bump in the `directory`, `Cabal`, and `process`
submodules.
Original author: Tamar Christina <tamar@zhox.com>
Test Plan: ./validate
Reviewers: bgamari, RyanGlScott, austin
Subscribers: hvr, RyanGlScott, thomie, #ghc_windows_task_force
Differential Revision: https://phabricator.haskell.org/D2938
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
In this case we are building a map, for which `foldl'` is much better
suited. This has a small but consistent impact on compiler allocations,
```
-1 s.d. ----- -0.161%
+1 s.d. ----- -0.011%
Average ----- -0.086%
```
Test Plan: Validate
Reviewers: austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2967
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Manipulations of `FreeRegs` values are all just bit-operations on a
word. Turning these `foldr`s into `foldl'`s has a very small but consistent
effect on compiler allocations,
```
-1 s.d. ----- -0.065%
+1 s.d. ----- -0.018%
Average ----- -0.042%
```
Test Plan: Validate
Reviewers: austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D2966
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
foldr generally isn't a good choice for folds where the result can't be
consumed incrementally. This gives a very modest improvement in
compiler allocations,
```
-1 s.d. ----- -0.182%
+1 s.d. ----- -0.050%
Average ----- -0.116%
```
This is clearly semantics-preserving since we are constructing a set.
Test Plan: Validate
Reviewers: austin
Subscribers: dfeuer, thomie
Differential Revision: https://phabricator.haskell.org/D2965
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
D3001 accidentally changed the meaning of `containsSpan`. Revert
that change.
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3015
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
It turns out that D2974 broke this program
(see https://phabricator.haskell.org/rGHC729a5e452db5#58801):
```lang=haskell
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import GHC.Exts (Constraint)
$([d| data Dec13 :: (* -> Constraint) -> * where
MkDec13 :: c a => a -> Dec13 c
|])
```
This was actually due to a long-standing bug in `hsSyn/Convert` that put
unnecessary `forall`s in front of GADT constructors that didn't have any
explicitly quantified type variables.
This cargo-cults the code in `Convert` that handles `ForallT` and adapts
it to `ForallC`. Fixes #13123 (for real this time).
Test Plan: make test TEST=T13123
Reviewers: goldfire, austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3002
GHC Trac Issues: #13123
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
RyanGlScott reported a failure:
```
Could not find module 'Prelude'; Perhaps you haven't
installed the "dyn" libraries for package ‘base-4.10.0.0’?
```
This might fix it.
Test Plan: harbormaster
Reviewers: austin, bgamari, thomie, RyanGlScott
Reviewed By: RyanGlScott
Subscribers: thomie, simonmar
Differential Revision: https://phabricator.haskell.org/D3013
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: harbormaster
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3004
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: harbormaster
Reviewers: austin, ezyang, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3005
GHC Trac Issues: #13102
|
|
|
|
|
|
|
|
|
|
|
|
| |
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3007
GHC Trac Issues: #12979
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Commit d3b546b1a605 added a "scrutinee constant folding" pass
that rewrites a case expression whose scrutinee is an expression like
x +# 3#. But case expressions are supposed to have their alternatives in
sorted order, so when the scrutinee is (for example) negateInt# x#, we
need to re-sort the alternatives after mapping their values.
This showed up as a core lint failure when compiling System.Process.Posix:
isSigIntQuit n = sig == sigINT || sig == sigQUIT
where sig = fromIntegral (-n)
Data.List.sortBy is supposed to be linear-time on sorted or reverse-sorted
input, so it is probably not worth doing anything more clever than this.
Test Plan: Added a new test T13170 for the above case.
Reviewers: austin, hsyl20, simonpj, bgamari
Reviewed By: hsyl20, simonpj, bgamari
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D3008
GHC Trac Issues: #13170
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Test Plan: T13172
Reviewers: rwbarton, simonpj, austin, bgamari
Reviewed By: simonpj, bgamari
Subscribers: simonpj, thomie
Differential Revision: https://phabricator.haskell.org/D3009
GHC Trac Issues: #13172
|
| |
|
| |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
This just reorders some inequality checks to make the common case
cheaper.
The results are quite dramatic for #11095, but that's probably because
something else is causing it to do too much work.
Before (full https://phabricator.haskell.org/P136):
```
13,589,495,832 bytes allocated in the heap
```
After (full https://phabricator.haskell.org/P137):
```
7,885,575,872 bytes allocated in the heap
```
This is with `BuildFlavour = devel2`, so take it with a
a grain of salt.
For reference, with no `-g` I get:
```
155,703,112 bytes allocated in the heap
```
so we're still quite a way off.
Test Plan:
harbormaster
I still have to test locally
Reviewers: austin, bgamari
Subscribers: thomie, simonmar
Differential Revision: https://phabricator.haskell.org/D3001
GHC Trac Issues: #11095
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
This patch is a refinement of the original commit (which
was reverted):
commit 6b976eb89fe72827f226506d16d3721ba4e28bab
Date: Fri Jan 13 08:56:53 2017 +0000
Record evaluated-ness on workers and wrappers
In Trac #13027, comment:20, I noticed that wrappers created after
demand analysis weren't recording the evaluated-ness of strict
constructor arguments. In the ticket that led to a (debatable)
Lint error but in general the more we know about evaluated-ness
the better we can optimise.
This commit adds that info
* both in the worker (on args)
* and in the wrapper (on CPR result patterns).
See Note [Record evaluated-ness in worker/wrapper] in WwLib
On the way I defined Id.setCaseBndrEvald, and used it to shorten
the code in a few other places
Then I added test T13077a to test the CPR aspect of this patch,
but I found that Lint failed!
Reason: simpleOptExpr was discarding evaluated-ness info on
lambda binders because zapFragileIdInfo was discarding an
Unfolding of (OtherCon _). But actually that's a robust
unfolding; there is no need to discard it. To fix this:
* zapFragileIdInfo only zaps fragile unfoldings
* Replace isClosedUnfolding with isFragileUnfolding (the latter
is just the negation of the former, but the nomenclature is
more consistent). Better documentation too
Note [Fragile unfoldings]
* And Simplify.simplLamBndr can now look at isFragileUnfolding
to decide whether to use the longer route of simplUnfolding.
For some reason perf/compiler/T9233 improves in compile-time
allocation by 10%. Hooray
Nofib: essentially no change:
--------------------------------------------------------------------------------
Program Size Allocs Runtime Elapsed TotalMem
--------------------------------------------------------------------------------
cacheprof +0.0% -0.3% +0.9% +0.4% +0.0%
--------------------------------------------------------------------------------
Min +0.0% -0.3% -2.4% -2.4% +0.0%
Max +0.0% +0.0% +9.8% +11.4% +2.4%
Geometric Mean +0.0% -0.0% +1.1% +1.0% +0.0%
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
Summary:
A bug was introduced in GHC 8.0 in which Template Haskell-quoted type
signatures would quantify _all_ their type variables, even the implicit ones.
This would cause splices like this:
```
$([d| idProxy :: forall proxy (a :: k). proxy a -> proxy a
idProxy x = x
|])
```
To splice back in something that was slightly different:
```
idProxy :: forall k proxy (a :: k). proxy a -> proxy a
idProxy x = x
```
Notice that the kind variable `k` is now explicitly quantified! What's worse,
this now requires the `TypeInType` extension to be enabled.
This changes the behavior of Template Haskell quoting to never explicitly
quantify type variables which are implicitly quantified in the source.
There are some other places where this behavior pops up too, including
class methods, type ascriptions, `SPECIALIZE` pragmas, foreign imports,
and pattern synonynms (#13018), so I fixed those too.
Fixes #13018 and #13123.
Test Plan: ./validate
Reviewers: simonpj, goldfire, austin, bgamari
Reviewed By: simonpj, goldfire
Subscribers: simonpj, mpickering, thomie
Differential Revision: https://phabricator.haskell.org/D2974
GHC Trac Issues: #13018, #13123
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| |
We've noticed that `checkFamInstConsistency` takes 6% of
overall build time on our codebase.
I've poked around for a bit and most of type family
instances are `Rep` from `Generics`. I think those are
unavoidable, so I don't think we can have less of them.
I also looked at the code and noticed a simple algorithmic
improvement can be made. The algorithm is pretty simple:
we take all the family instances from one module (`M1`)
and test it against another module (`M2`).
The cost of that is dominated by the size of `M1`, because
for each instance in `M1` we look it up in the type family
env from `M2`, and lookup is cheap.
If `M1` is bigger than `M2`, that's suboptimal, so after
my change we always iterate through the smaller set.
This drives down the cost of `checkFamInstConsistency`
to 2%.
Test Plan: harbormaster
Reviewers: simonmar, simonpj, goldfire, rwbarton, bgamari, ezyang, austin
Reviewed By: rwbarton, ezyang
Subscribers: ezyang, thomie
Differential Revision: https://phabricator.haskell.org/D2833
|
| |
|