
Andreas Klebinger pushed to branch wip/andreask/spec_tyfams at Glasgow Haskell Compiler / GHC Commits: fd64667d by Vladislav Zavialov at 2025-05-20T03:25:08-04:00 Allow the 'data' keyword in import/export lists (#25899) This patch introduces the 'data' namespace specifier in import and export lists. The intended use is to import data constructors without their parent type constructors, e.g. import Data.Proxy as D (data Proxy) type DP = D.Proxy -- promoted data constructor Additionally, it is possible to use 'data' to explicitly qualify any data constructors or terms, incl. operators and field selectors import Prelude (Semigroup(data (<>))) import Data.Function (data (&)) import Data.Monoid (data Dual, data getDual) x = Dual "Hello" <> Dual "World" & getDual The implementation mostly builds on top of the existing logic for the 'type' and 'pattern' namespace specifiers, plus there are a few tweaks to how we generate suggestions in error messages. - - - - - acc86753 by Ben Gamari at 2025-05-20T03:25:51-04:00 compiler: Use field selectors when creating BCOs This makes it easier to grep for these fields. - - - - - 60a55fd7 by Ben Gamari at 2025-05-20T03:25:51-04:00 compiler: Clarify BCO size Previously the semantics and size of StgBCO was a bit unclear. Specifically, the `size` field was documented to contain the size of the bitmap whereas it was actually the size of the closure *and* bitmap. Additionally, it was not as clear as it could be that the bitmap was a full StgLargeBitmap with its own `size` field. - - - - - ac9fb269 by Simon Peyton Jones at 2025-05-20T09:19:04-04:00 Track rewriter sets more accurately in constraint solving This MR addresses #26003, by refactoring the arcane intricacies of Note [Equalities with incompatible kinds]. NB: now retitled to Note [Equalities with heterogeneous kinds]. and the main Note for this MR. In particular: * Abandon invariant (COERCION-HOLE) in Note [Unification preconditions] in GHC.Tc.Utils.Unify. * Abandon invariant (TyEq:CH)) in Note [Canonical equalities] in GHC.Tc.Types.Constraint. * Instead: add invariant (REWRITERS) to Note [Unification preconditions]: unify only if the constraint has an empty rewriter set. Implementation: * In canEqCanLHSFinish_try_unification, skip trying unification if there is a non-empty rewriter set. * To do this, make sure the rewriter set is zonked; do so in selectNextWorkItem, which also deals with prioritisation. * When a coercion hole is filled, kick out inert equalities that have that hole as a rewriter. It might now be unlocked and available to unify. * Remove the ad-hoc `ch_hetero_kind` field of `CoercionHole`. * In `selectNextWorkItem`, priorities equalities withan empty rewriter set. * Defaulting: see (DE6) in Note [Defaulting equalities] and Note [Limited defaulting in the ambiguity check] * Concreteness checks: there is some extra faff to try to get decent error messages when the FRR (representation-polymorphism) checks fail. In partiular, add a "When unifying..." explanation when the representation-polymorphism check arose from another constraint. - - - - - 86406f48 by Cheng Shao at 2025-05-20T09:19:47-04:00 rts: fix rts_clearMemory logic when sanity checks are enabled This commit fixes an RTS assertion failure when invoking rts_clearMemory with +RTS -DS. -DS implies -DZ which asserts that free blocks contain 0xaa as the designated garbage value. Also adds the sanity way to rts_clearMemory test to prevent future regression. Closes #26011. ChatGPT Codex automatically diagnosed the issue and proposed the initial patch in a single shot, given a GHC checkout and the following prompt: --- Someone is reporting the following error when attempting to use `rts_clearMemory` with the RTS option `-DS`: ``` test.wasm: internal error: ASSERTION FAILED: file rts/sm/Storage.c, line 1216 (GHC version 9.12.2.20250327 for wasm32_unknown_wasi) Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug ``` What's the culprit? How do I look into this issue? --- I manually reviewed & revised the patch, tested and submitted it. - - - - - 7147370b by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: do not allocate strings in bytecode assembler This patch refactors the compiler to avoid allocating iserv buffers for BCONPtrStr at assemble-time. Now BCONPtrStr ByteStrings are recorded as a part of CompiledByteCode, and actual allocation only happens at link-time. This refactoring is necessary for adding bytecode serialization functionality, as explained by the revised comments in this commit. - - - - - a67db612 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: make bc_strs serializable This commit makes the bc_strs field in CompiledByteCode serializable; similar to previous commit, we preserve the ByteString directly and defer the actual allocation to link-time, as mentioned in updated comment. - - - - - 5faf34ef by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: make bc_itbls serializable This commit makes bc_itbls in CompiledByteCode serializable. A dedicated ConInfoTable datatype has been added in ghci which is the recipe for dynamically making a datacon's info table, containing the payload of the MkConInfoTable iserv message. - - - - - 2abaf8c1 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: remove FFIInfo bookkeeping in BCO This commit removes the bc_ffis field from CompiledByteCode completely, as well as all the related bookkeeping logic in GHC.StgToByteCode. bc_ffis is actually *unused* in the rest of GHC codebase! It is merely a list of FFIInfo, which is just a remote pointer of the libffi ffi_cif struct; once we allocate the ffi_cif struct and put its pointer in a CCALL instruction, we'll never free it anyway. So there is no point of bookkeeping. - - - - - adb9e4d2 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: make FFIInfo serializable in BCO This commit makes all the FFIInfo needed in CCALL instructions serializable. Previously, when doing STG to BCO lowering, we would allocate a libffi ffi_cif struct and keep its remote pointer as FFIInfo; but actually we can just keep the type signature as FFIInfo and defer the actual allocation to link-time. - - - - - 200f401b by Cheng Shao at 2025-05-20T17:22:19-04:00 ghci: remove redundant NewBreakModule message This commit removes the redundant NewBreakModule message from ghci: it just allocates two strings! This functionality can be implemented with existing MallocStrings in one iserv call. - - - - - ddaadca6 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: make breakpoint module name and unit id serializable This commit makes breakpoint module name and unit id serializable, in BRK_FUN instructions as well as ModBreaks. We can simply keep the module name and unit ids, and defer the buffer allocation to link time. - - - - - a0fde202 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: remove unused newModule This commit removes the now unused newModule function from GHC. - - - - - 68c8f140 by Cheng Shao at 2025-05-20T17:22:19-04:00 compiler: add BCONPtrFS for interned top level string literals in BCO This commit adds BCONPtrFS as a BCO non-pointer literal kind, which has the same semantics of BCONPtrStr, except it contains a FastString instead of a ByteString. By using BCONPtrFS to represent top level string literals that are already FastString in the compilation pipeline, we enjoy the FastString interning logic and avoid allocating a bunch of redundant ByteStrings for the same FastStrings, especially when we lower the BRK_FUN instruction. - - - - - f2b532bc by Peng Fan at 2025-05-20T17:23:15-04:00 hadrian: enable GHCi for loongarch64 - - - - - 8ded2330 by kwxm at 2025-05-20T17:24:07-04:00 Fix bugs in `integerRecipMod` and `integerPowMod` This fixes #26017. * `integerRecipMod x 1` now returns `(# 1 | #)` for all x; previously it incorrectly returned `(# | () #)`, indicating failure. * `integerPowMod 0 e m` now returns `(# | () #)` for e<0 and m>1, indicating failure; previously it incorrectly returned `(# 0 | #)`. - - - - - c9abb87c by Andreas Klebinger at 2025-05-20T17:24:50-04:00 Specialise: Don't float out constraint components. It was fairly complex to do so and it doesn't seem to improve anything. Nofib allocations were unaffected as well. See also Historical Note [Floating dictionaries out of cases] - - - - - 202b201c by Andreas Klebinger at 2025-05-21T10:16:14-04:00 Interpreter: Add limited support for direct primop evaluation. This commit adds support for a number of primops directly to the interpreter. This avoids the indirection of going through the primop wrapper for those primops speeding interpretation of optimized code up massively. Code involving IntSet runs about 25% faster with optimized core and these changes. For core without breakpoints it's even more pronouced and I saw reductions in runtime by up to 50%. Running GHC itself in the interpreter was sped up by ~15% through this change. Additionally this comment does a few other related changes: testsuite: * Run foundation test in ghci and ghci-opt ways to test these primops. * Vastly expand the foundation test to cover all basic primops by comparing result with the result of calling the wrapper. Interpreter: * When pushing arguments for interpreted primops extend each argument to at least word with when pushing. This avoids some issues with big endian. We can revisit this if it causes performance issues. * Restructure the stack chunk check logic. There are now macros for read accesses which might cross stack chunk boundries and macros which omit the checks which are used when we statically know we access an address in the current stack chunk. - - - - - 67a177b4 by sheaf at 2025-05-21T10:17:04-04:00 QuickLook: do a shape test before unifying This commit ensures we do a shape test before unifying. This ensures we don't try to unify a TyVarTv with a non-tyvar, e.g. alpha[tyv] := Int On the way, we refactor simpleUnifyCheck: 1. Move the checkTopShape check into simpleUnifyCheck 2. Refactors simpleUnifyCheck to return a value of the new type SimpleUnifyResult type. Now, simpleUnifyCheck returns "can unify", "cannot unify" or "dunno" (with "cannot unify" being the new result it can return). Now: - touchabilityTest is included; it it fails we return "cannot unify" - checkTopShape now returns "cannot unify" instead of "dunno" upon failure 3. Move the call to simpleUnifyCheck out of checkTouchableTyVarEq. After that, checkTouchableTyVarEq becames a simple call to checkTyEqRhs, so we inline it. This allows the logic in canEqCanLHSFinish_try_unification to be simplified. In particular, we now avoid calling 'checkTopShape' twice. Two further changes suggested by Simon were also implemented: - In canEqCanLHSFinish, if checkTyEqRhs returns PuFail with 'do_not_prevent_rewriting', we now **continue with this constraint**. This allows us to use the constraint for rewriting. - checkTyEqRhs now has a top-level check to avoid flattening a tyfam app in a top-level equality of the form alpha ~ F tys, as this is going around in circles. This simplifies the implementation without any change in behaviour. Fixes #25950 Fixes #26030 - - - - - 4020972c by sheaf at 2025-05-21T10:17:04-04:00 FixedRuntimeRepError: omit unhelpful explanation This commit tweaks the FixedRuntimeRepError case of pprTcSolverReportMsg, to avoid including an explanation which refers to a type variable that appears nowhere else. For example, the old error message could look like the following: The pattern binding does not have a fixed runtime representation. Its type is: T :: TYPE R Cannot unify ‘R’ with the type variable ‘c0’ because the former is not a concrete ‘RuntimeRep’. With this commit, we now omit the last two lines, because the concrete type variable (here 'c0') does not appear in the type displayed to the user (here 'T :: TYPE R'). - - - - - 8b289b41 by Andreas Klebinger at 2025-05-21T17:32:13+02:00 Specialise: Improve specialisation by refactoring interestingDict This MR addresses #26051, which concerns missed type-class specialisation. The main payload of the MR is to completely refactor the key function `interestingDict` in GHC.Core.Opt.Specialise The main change is that we now also look at the structure of the dictionary we consider specializing on, rather than only the type. See the big `Note [Interesting dictionary arguments]` - - - - - 158 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/HsToCore/Breakpoints.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Default.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/Language/Haskell/Syntax/ImpExp.hs - docs/users_guide/9.14.1-notes.rst - docs/users_guide/exts/explicit_namespaces.rst - docs/users_guide/exts/pattern_synonyms.rst - hadrian/src/Oracles/Flag.hs - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Disassembler.c - rts/Interpreter.c - rts/PrimOps.cmm - rts/include/rts/Bytecodes.h - rts/include/rts/storage/Closures.h - rts/sm/Storage.h - testsuite/tests/bytecode/T22376/all.T - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/dependent/should_fail/T11471.stderr - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ffi/should_run/all.T - + testsuite/tests/ghci/all.T - + testsuite/tests/ghci/ghci-mem-primops.hs - + testsuite/tests/ghci/ghci-mem-primops.script - + testsuite/tests/ghci/ghci-mem-primops.stdout - testsuite/tests/indexed-types/should_fail/T8227.stderr - testsuite/tests/indexed-types/should_fail/T9662.stderr - + testsuite/tests/lib/integer/T26017.hs - + testsuite/tests/lib/integer/T26017.stdout - testsuite/tests/lib/integer/all.T - testsuite/tests/lib/integer/integerRecipMod.hs - testsuite/tests/lib/integer/integerRecipMod.stdout - testsuite/tests/module/T21826.stderr - testsuite/tests/numeric/should_run/all.T - testsuite/tests/numeric/should_run/foundation.hs - testsuite/tests/numeric/should_run/foundation.stdout - testsuite/tests/partial-sigs/should_fail/T14040a.stderr - testsuite/tests/partial-sigs/should_fail/T14584.stderr - testsuite/tests/perf/should_run/ByteCodeAsm.hs - + testsuite/tests/perf/should_run/SpecTyFamRun.hs - + testsuite/tests/perf/should_run/SpecTyFamRun.stdout - + testsuite/tests/perf/should_run/SpecTyFam_Import.hs - testsuite/tests/perf/should_run/all.T - testsuite/tests/polykinds/T14172.stderr - testsuite/tests/polykinds/T14846.stderr - testsuite/tests/rename/should_compile/T22581d.stdout - + testsuite/tests/rename/should_compile/T25899a.hs - + testsuite/tests/rename/should_compile/T25899b.hs - + testsuite/tests/rename/should_compile/T25899c.hs - + testsuite/tests/rename/should_compile/T25899c_helper.hs - + testsuite/tests/rename/should_compile/T25899d.script - + testsuite/tests/rename/should_compile/T25899d.stdout - testsuite/tests/rename/should_compile/all.T - testsuite/tests/rename/should_fail/T22581a.stderr - testsuite/tests/rename/should_fail/T22581b.stderr - + testsuite/tests/rename/should_fail/T25899e1.hs - + testsuite/tests/rename/should_fail/T25899e1.stderr - + testsuite/tests/rename/should_fail/T25899e2.hs - + testsuite/tests/rename/should_fail/T25899e2.stderr - + testsuite/tests/rename/should_fail/T25899e3.hs - + testsuite/tests/rename/should_fail/T25899e3.stderr - + testsuite/tests/rename/should_fail/T25899e_helper.hs - + testsuite/tests/rename/should_fail/T25899f.hs - + testsuite/tests/rename/should_fail/T25899f.stderr - + testsuite/tests/rename/should_fail/T25899f_helper.hs - testsuite/tests/rename/should_fail/all.T - testsuite/tests/rep-poly/RepPolyArgument.stderr - testsuite/tests/rep-poly/RepPolyBackpack1.stderr - testsuite/tests/rep-poly/RepPolyBinder.stderr - testsuite/tests/rep-poly/RepPolyDoBind.stderr - testsuite/tests/rep-poly/RepPolyDoBody1.stderr - testsuite/tests/rep-poly/RepPolyDoBody2.stderr - testsuite/tests/rep-poly/RepPolyLeftSection2.stderr - testsuite/tests/rep-poly/RepPolyMagic.stderr - testsuite/tests/rep-poly/RepPolyMcBind.stderr - testsuite/tests/rep-poly/RepPolyMcBody.stderr - testsuite/tests/rep-poly/RepPolyMcGuard.stderr - testsuite/tests/rep-poly/RepPolyNPlusK.stderr - testsuite/tests/rep-poly/RepPolyPatBind.stderr - testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr - testsuite/tests/rep-poly/RepPolyRightSection.stderr - testsuite/tests/rep-poly/RepPolyRule1.stderr - testsuite/tests/rep-poly/RepPolyTuple.stderr - testsuite/tests/rep-poly/RepPolyTuple4.stderr - testsuite/tests/rep-poly/RepPolyTupleSection.stderr - testsuite/tests/rep-poly/RepPolyWrappedVar.stderr - testsuite/tests/rep-poly/T11473.stderr - testsuite/tests/rep-poly/T12709.stderr - testsuite/tests/rep-poly/T12973.stderr - testsuite/tests/rep-poly/T13233.stderr - testsuite/tests/rep-poly/T13929.stderr - testsuite/tests/rep-poly/T14561.stderr - testsuite/tests/rep-poly/T14561b.stderr - testsuite/tests/rep-poly/T17817.stderr - testsuite/tests/rep-poly/T19615.stderr - testsuite/tests/rep-poly/T19709b.stderr - testsuite/tests/rep-poly/T21906.stderr - testsuite/tests/rep-poly/T23903.stderr - testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr - + testsuite/tests/simplCore/should_compile/T26051.hs - + testsuite/tests/simplCore/should_compile/T26051.stderr - + testsuite/tests/simplCore/should_compile/T26051_Import.hs - testsuite/tests/simplCore/should_compile/all.T - testsuite/tests/simplCore/should_compile/simpl017.stderr - testsuite/tests/typecheck/no_skolem_info/T14040.stderr - testsuite/tests/typecheck/should_compile/T25266a.stderr - + testsuite/tests/typecheck/should_compile/T26030.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T16204c.stderr - + testsuite/tests/typecheck/should_fail/T25950.hs - + testsuite/tests/typecheck/should_fail/T25950.stderr - testsuite/tests/typecheck/should_fail/T7696.stderr - testsuite/tests/typecheck/should_fail/T8603.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/check-exact/ExactPrint.hs - utils/genprimopcode/Main.hs - utils/genprimopcode/Syntax.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be412c3ea2868c38e5c0198e19b89df... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be412c3ea2868c38e5c0198e19b89df... You're receiving this email because of your account on gitlab.haskell.org.