Commits on Source (54)
-
The BL constructor carried unused data in its third argument.
eb612fbc -
It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it
b0300503 -
Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998
842e119b -
Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592
24e89c40 -
This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should.
04f5bb85 -
This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity.
9a757a27 -
cd512234
-
Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002
8a8ff8f2 -
This pragma was accidentally introduced in 648fd73a The top-level cost centres lead to a lack of optimisation when compiling with profiling.
7b079378 -
haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler
c872e09b -
8c87d4e1
-
When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725.
568de8a5 -
This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030
c8a8727e -
21fc180b
-
This is possible now that #22229 is fixed.
d640a3b6 -
After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. The residency of T24471 increases by 13% because we now load `AnnLookup` from its interface file, which transitively loads the whole TH AST. Unavoidable and not terrible, I think. Metric Increase: T24471
33fee6a2 -
If a user has configured CDPATH on their system then `cd lib` may change into an unexpected directory during the installation process. If you write `cd ./lib` then it will not consult `CDPATH` to determine what you mean. I have added a check on ghcup-ci to verify that the bindist installation works in this situation. Fixes #24951
383c01a8 -
The pervasive usage of DynFlags (the parsed command-line options passed to ghc) blurs the border between different components of Haddock, and especially those that focus solely on printing text on the screen. In order to improve the understanding of the real dependencies of a function, the pretty-printer options are made concrete earlier in the pipeline instead of late when pretty-printing happens. This also has the advantage of clarifying which functions actually require DynFlags for purposes other than pretty-printing, thus making the interactions between Haddock and GHC more understandable when exploring the code base. See Henry, Ericson, Young. "Modularizing GHC". https://hsyl20.fr/home/files/papers/2022-ghc-modularity.pdf. 2022
5759133f -
To allow rules to be written on the concrete implementation of `compare` for `Int` and `Word`, we need to have an `INLINE [1]` pragma on these functions, following the `matching_overloaded_methods_in_rules` note in `GHC.Classes`. CLC proposal https://github.com/haskell/core-libraries-committee/issues/179 Fixes #22643
749e089b -
db033639
-
Improves the error message for when `ghc-toolchain` fails to read a valid `Target` value from a file (in doFormat mode).
14308a8f -
6e7cfff1
-
It is better to fail earlier if the configure step fails rather than carrying on for a more obscure error message.
958d6931 -
f48d157d
-
It is non-obvious whether the toolchain configuration should use full-paths to tools or simply their names. In addressing #24574, we've decided to prefer executable names over paths, ultimately, because the bindist configure script already does this, thus is the default in ghcs out there. Updates the in-tree configure script to prefer tool names (`AC_CHECK_TOOL` rather than `AC_PATH_TOOL`) and `ghc-toolchain` to ignore the full-path-result of `findExecutable`, which it previously used over the program name. This change doesn't undo the fix in bd92182c because `AC_CHECK_TOOL` still takes into account the target triples, unlike `AC_CHECK_PROG/AC_PATH_PROG`.
665e653e -
We introduced a configuration step for the javascript preprocessor, but only did so for the in-tree configure script. This commit makes it so that we also configure the javascript preprocessor in the configure shipped in the compiler bindist.
463716c2 -
LlvmTarget was being set and substituted in the in-tree configure, but not in the configure shipped in the bindist. We want to set the LlvmTarget to the canonical LLVM name of the platform that GHC is targetting. Currently, that is going to be the boostrapped llvm target (hence the code which sets LlvmTarget=bootstrap_llvm_target).
e99cd73d -
4199aafe
-
f599d816
-
haddock: Move the usage of mkParserOpts directly to ppHyperlinkedModuleSource in order to avoid passing a whole DynFlags Follow up to !12931
8f4b799d -
This will be reintroduced with a properly ignored commit when the cabal files are themselves formatted for good.
210cf1cd -
Sign hints for parameters are in the second component of the pair. Fixes #23034
7fe85b13 -
When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor. This is potentially helpful for performance and required to fix #24870.
1bfa9111 -
`compareLength xs n` is a safer and faster alternative to `compare (length xs) n`. The latter would force and traverse the entire spine (potentially diverging), while the former traverses as few elements as possible. The implementation is carefully designed to maintain as much laziness as possible. As per https://github.com/haskell/core-libraries-committee/issues/257
caf44a2d -
The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode -------------------------
f4606ae0 -
This commit removes idiosyncrasies that have accumulated with the years in how import statements were laid out, and defines clear but simple guidelines in the CONTRIBUTING.md file.
0e424304 -
I must have fumbled my tabs when I copy/pasted the issue number in 8c87d4e1.
9b8ddaaf -
b0944623
-
sed on BSD systems (such as darwin) does not support the + operation. Therefore we take the simple minded approach of manually expanding group+ to groupgroup*. Fixes #24999
77ce65a5 -
The version check was previously broken so the toolchain was not detected at all.
bdfe4a9e -
One dependency (c-ares) changed where it hosted the releases which breaks the build with the old nixpkgs commit.
07e03a69 -
144afed7
-
- Without TNTC (tables-next-to-code), we must be careful to not duplicate labels in pprNatCmmDecl. Especially, as a CmmProc is identified by the label of its entry block (and not of its info table), we can't reuse the same label to delimit the block end and the proc end. - We generate debug infos from Cmm blocks. However, when asm-shortcutting is enabled, some blocks are dropped at the asm codegen stage and some labels in the DebugBlocks become missing. We fix this by filtering the generated debug-info after the asm codegen to only keep valid infos. Also add some related documentation.
eebe1658 -
6e86d82b
-
9e4b4b0a
-
50caef3e
-
This updates the os-string submodule to 2.0.4 which removes the usage of `TemplateHaskell` pragma.
37139b17 -
Unverified870e519b
-
Unverified82ca6313
-
Andrei Borzenkov authoredUnverifiedc83c1d2f
Showing
- .gitlab-ci.yml 2 additions, 2 deletions.gitlab-ci.yml
- .gitlab/ci.sh 1 addition, 1 deletion.gitlab/ci.sh
- .gitlab/darwin/nix/sources.json 3 additions, 3 deletions.gitlab/darwin/nix/sources.json
- .gitlab/darwin/toolchain.nix 3 additions, 0 deletions.gitlab/darwin/toolchain.nix
- .gitlab/generate-ci/gen_ci.hs 1 addition, 0 deletions.gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml 80 additions, 11 deletions.gitlab/jobs.yaml
- compiler/GHC/Builtin/Names/TH.hs 12 additions, 4 deletionscompiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps.hs 0 additions, 1 deletioncompiler/GHC/Builtin/PrimOps.hs
- compiler/GHC/ByteCode/Instr.hs 1 addition, 1 deletioncompiler/GHC/ByteCode/Instr.hs
- compiler/GHC/Cmm/CLabel.hs 24 additions, 4 deletionscompiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/DebugBlock.hs 15 additions, 15 deletionscompiler/GHC/Cmm/DebugBlock.hs
- compiler/GHC/Cmm/Parser.y 5 additions, 2 deletionscompiler/GHC/Cmm/Parser.y
- compiler/GHC/CmmToAsm.hs 12 additions, 3 deletionscompiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs 4 additions, 4 deletionscompiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs 5 additions, 5 deletionscompiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs 3 additions, 3 deletionscompiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs 8 additions, 2 deletionscompiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/PPC/Ppr.hs 8 additions, 2 deletionscompiler/GHC/CmmToAsm/PPC/Ppr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs 69 additions, 41 deletionscompiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/Core/DataCon.hs 1 addition, 1 deletioncompiler/GHC/Core/DataCon.hs